Re: [Haskell-cafe] Constructing a datatype given just its constructor as a string?

2007-06-25 Thread Benja Fallenstein

Hi Hugh,

2007/6/25, Donald Bruce Stewart [EMAIL PROTECTED]:

hughperkins:

Just noticed that all my responses have been going only to
Neil, not  to the group.
Anyway, the jist of our conversation was that it's not
possible to create arbitrary datatypes/constructors from
strings in Haskell.  Can anyone deny/confirm?

Anyway there was a thread on this last week.


That thread starting here:

http://www.haskell.org/pipermail/haskell-cafe/2007-June/026777.html

The takeaway was Stefan O'Rear's suggestion that if you don't want to
create a table of datatypes manually, you can use hs-plugins --
something along the lines of

data Foo = forall a. MyClass a = Foo a
read' typeName s = eval (Foo (gread \ ++ s ++ \ ::  ++ typeName
++ )) :: Foo

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Daniil Elovkov

2007/6/25, Michael T. Richter [EMAIL PROTECTED]:


 Now I've got a situation I can't figure out how to resolve.  I want to have a 
set of actions which are executed sequentially, but which, before I even start 
to execute the first one, have been inspected for legality and/or plausibility. 
 Consider this kind of sequence:

 do
   x - performActionA
   y - performActionB
   z - performActionC
   return $ calculateStuff x y z

 Now obviously this is going to be in a monad of some kind.  Were this a 
regular, run-of-the-mill program I'd just use the IO monad.  But what I want to 
do instead is, before executing any of the perform* functions, check that the 
actions desired are actually permitted (or possible) given a set of 
circumstances.  For example let's say it's a permissions issue and 
performActionB can only be done if I'm root.  If I'm not root I don't want 
performActionA done because I can't complete the transaction.  (Maybe ActionA 
is non-reversible, say.)  Or let's say this is code that's accessing databases 
on the network.  If the network link to C can't be established, I don't want to 
screw around with A and B's links at all -- it's too expensive, too 
time-consuming or whatever.

 Were I programming this in C, C++, Python, Ruby, etc. I could do this in my 
sleep.  Functions are addresses (C/C++) or objects with an ID (Python/Ruby) so 
it's possible to take them and do some kind of check based on identities before 
executing things (although the scaffolding around this would be nontrivial in 
any of these languages except, possibly, Ruby).  Functions in Haskell don't 
have this property, however, so I can't figure out what I'd do to perform 
similar work.  I'm sure there's a way to do it, but I just can't see it.



Hello, I would suggest defining your own data type an instance of
monad. The sense of it would be 'sequantial IO operations which you
can do some checks on'.

It would have some flags and properties along with the IO computation
itself. Operations () and (=) would construct more complex
computations from simple ones, and since your data type is not opaque
to you, you could inspect those complex computations for properties,
too. Including synergetic ones, like 'this is never done, after that
has been invoked...'

And then you will have to have a conventional runYourMonad function,
which will be an IO computation. It could be the place, where the
validity check occurs.

The data type could be the list of operations, or probably a tree-like
structure to account for branching.

The downside is you would have to supply those flags, but you could
define some lifting functions, like
flag :: Flags - IO a - YourMonad a
do
 flag OnlyRoot ioOperation
 flag someComplexFlag anotherOperation


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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Tomasz Zielonka
On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:
 Imagine all performActions contain their checks somehow. Let
 performActionB take an argument.
 
   do
 x - performActionA
 y - performActionB x
 z - performActionC
 return $ calculateStuff x y z
 
 Now performActionB and its included check depend on x. That is, the check
 relies formally on the result of performActionA and thus check B must be
 performed after performActionA.

IIUC, this limitation of Monads was one of the reasons why John Hughes
introduced the new Arrow abstraction.

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Henning Thielemann

On Mon, 25 Jun 2007, Tomasz Zielonka wrote:

 On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:
  Imagine all performActions contain their checks somehow. Let
  performActionB take an argument.
 
do
  x - performActionA
  y - performActionB x
  z - performActionC
  return $ calculateStuff x y z
 
  Now performActionB and its included check depend on x. That is, the check
  relies formally on the result of performActionA and thus check B must be
  performed after performActionA.

 IIUC, this limitation of Monads was one of the reasons why John Hughes
 introduced the new Arrow abstraction.

How would this problem be solved using Arrows?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Wouter Swierstra

Hi Michael,

On 25 Jun 2007, at 06:39, Michael T. Richter wrote:


do
  x - performActionA
  y - performActionB
  z - performActionC
  return $ calculateStuff x y z


I don't know about you're exact example, but here's what I'd do.

Control.Monad has functions like when, unless, and guard that you can  
use to check whether the precondition holds. I find an ifM  
combinator quite useful sometimes:


ifM :: Monad m = m Bool - m a - m a - ma
ifM cond thenBranch elseBranch = do
  b - cond
  if cond
then thenBranch
else elseBranch

If everything checks out, you can then execute your A, B, and C actions.

I don't think you really want arrows here. The right idiom is  
applicative functors (see Control.Applicative). You could then write  
the above as:


calculateStuff $ x * y * z

Hope this helps,

  Wouter

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Pepe Iborra


There is a related discussion, with a lot of pointers, in a recent  
D.Piponi blog post:


http://sigfpe.blogspot.com/2007/04/homeland-security-threat-level- 
monad.html




On 25/06/2007, at 10:58, peterv wrote:

I'm baffled. So using the Arrow abstraction (which I don't know  
yet) would
solve this problem? How can (perfectActionB x) be checked with  
without ever
executing performActionA which evaluates to x? This can only be  
done when x

is a constant expression no?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Tomasz Zielonka
Sent: Monday, June 25, 2007 10:43 AM
To: Henning Thielemann
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Practical Haskell question.

On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:

Imagine all performActions contain their checks somehow. Let
performActionB take an argument.


 do
   x - performActionA
   y - performActionB x
   z - performActionC
   return $ calculateStuff x y z


Now performActionB and its included check depend on x. That is,  
the check
relies formally on the result of performActionA and thus check B  
must be

performed after performActionA.


IIUC, this limitation of Monads was one of the reasons why John Hughes
introduced the new Arrow abstraction.

Best regards
Tomek
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 22, 2007, at 3:11 PM, Brandon S. Allbery KF8NH wrote:

(1) any way to flag a pattern match as I know this is okay, don't  
warn about it without shutting off pattern match warnings completely?


GHC doesn't issue warnings about patterns on the left of =

For example, the following code compiles just fine with ghc -Wall - 
Werror, but the use of Just m generates a run-time exception:



module Main where

a :: [(Int,Int)]
a = [(2*n,n) | n - [1..100]]

m :: Int
Just m = lookup 3 a

main :: IO ()
main = putStrLn $ show m


I'd take this as a ghc feature, not a bug. When I use this construct  
in practice, I have a proof in mind that the pattern match cannot  
fail for my data, but I can't express the proof in Haskell's type  
system. I'm ok with skipping writing that proof.


The difference here is programmer intent. While a missing pattern  
case can often be an oversight, there's no way to put both cases here  
to the left of =, so the programmer clearly intends this code as  
written.


(An example of a language with a Turing complete type system is Qi:  
http://www.lambdassociates.org/
As pointed out elsewhere in this thread, it is unreasonable/ 
undecidable to expect a type system to work out arbitrarily difficult  
issues for you automatically. Some work is required, programming in  
the type system. They extend this point of view.)



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


RE: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Michael T. Richter
OK, just to prevent this getting side-tracked: I'm absolutely
uninterested in the results of performActionA before determining if
performActionB is permitted/possible/whatever.  Think more in terms of
security permissions or resource availability/claiming than in terms of
chaining results.  I want to know before I begin to collect the results
of performAction* that I will actually stand a chance at getting results
at all.

On Mon, 2007-25-06 at 10:58 +0200, peterv wrote:

 I'm baffled. So using the Arrow abstraction (which I don't know yet) would
 solve this problem? How can (perfectActionB x) be checked with without ever
 executing performActionA which evaluates to x? This can only be done when x
 is a constant expression no?
 
 -Original Message-
 From: [EMAIL PROTECTED]
 [mailto:[EMAIL PROTECTED] On Behalf Of Tomasz Zielonka
 Sent: Monday, June 25, 2007 10:43 AM
 To: Henning Thielemann
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Practical Haskell question.
 
 On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:
  Imagine all performActions contain their checks somehow. Let
  performActionB take an argument.
  
do
  x - performActionA
  y - performActionB x
  z - performActionC
  return $ calculateStuff x y z
  
  Now performActionB and its included check depend on x. That is, the check
  relies formally on the result of performActionA and thus check B must be
  performed after performActionA.
 
 IIUC, this limitation of Monads was one of the reasons why John Hughes
 introduced the new Arrow abstraction.
 
 Best regards
 Tomek
 ___
 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

-- 
Michael T. Richter [EMAIL PROTECTED] (GoogleTalk:
[EMAIL PROTECTED])
I'm not schooled in the science of human factors, but I suspect surprise
is not an element of a robust user interface. (Chip Rosenthal)


signature.asc
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] Practical Haskell question.

2007-06-25 Thread Benja Fallenstein

Hi Peter,

2007/6/25, peterv [EMAIL PROTECTED]:

I'm baffled. So using the Arrow abstraction (which I don't know yet) would
solve this problem? How can (perfectActionB x) be checked with without ever
executing performActionA which evaluates to x? This can only be done when x
is a constant expression no?


Arrows separate the action -- 'performActionB' -- from the argument --
'x', so you can look at the action before you have to compute the
argument to it. Of course, this means that you can no longer compute
the action from the argument -- that is, 'if x then performActionB
else performActionC' is something you can't directly do; you have to
use a choice primitive instead, which explicitly says use one of
these two arrows depending on what value this argument is, which then
lets the library check these two arrows before actually applying them
to an argument.

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


RE: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread peterv
I'm baffled. So using the Arrow abstraction (which I don't know yet) would
solve this problem? How can (perfectActionB x) be checked with without ever
executing performActionA which evaluates to x? This can only be done when x
is a constant expression no?

-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Tomasz Zielonka
Sent: Monday, June 25, 2007 10:43 AM
To: Henning Thielemann
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Practical Haskell question.

On Mon, Jun 25, 2007 at 10:29:14AM +0200, Henning Thielemann wrote:
 Imagine all performActions contain their checks somehow. Let
 performActionB take an argument.
 
   do
 x - performActionA
 y - performActionB x
 z - performActionC
 return $ calculateStuff x y z
 
 Now performActionB and its included check depend on x. That is, the check
 relies formally on the result of performActionA and thus check B must be
 performed after performActionA.

IIUC, this limitation of Monads was one of the reasons why John Hughes
introduced the new Arrow abstraction.

Best regards
Tomek
___
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] Practical Haskell question.

2007-06-25 Thread Henning Thielemann

On Mon, 25 Jun 2007, Daniil Elovkov wrote:

 2007/6/25, Michael T. Richter [EMAIL PROTECTED]:
 
   Now I've got a situation I can't figure out how to resolve.  I want to 
  have a set of actions which are executed sequentially, but which, before I 
  even start to execute the first one, have been inspected for legality 
  and/or plausibility.  Consider this kind of sequence:
 
   do
 x - performActionA
 y - performActionB
 z - performActionC
 return $ calculateStuff x y z
 
   Now obviously this is going to be in a monad of some kind.  Were this a 
  regular, run-of-the-mill program I'd just use the IO monad.  But what I 
  want to do instead is, before executing any of the perform* functions, 
  check that the actions desired are actually permitted (or possible) given a 
  set of circumstances.  For example let's say it's a permissions issue and 
  performActionB can only be done if I'm root.  If I'm not root I don't want 
  performActionA done because I can't complete the transaction.  (Maybe 
  ActionA is non-reversible, say.)  Or let's say this is code that's 
  accessing databases on the network.  If the network link to C can't be 
  established, I don't want to screw around with A and B's links at all -- 
  it's too expensive, too time-consuming or whatever.
 
   Were I programming this in C, C++, Python, Ruby, etc. I could do this in 
  my sleep.  Functions are addresses (C/C++) or objects with an ID 
  (Python/Ruby) so it's possible to take them and do some kind of check based 
  on identities before executing things (although the scaffolding around this 
  would be nontrivial in any of these languages except, possibly, Ruby).  
  Functions in Haskell don't have this property, however, so I can't figure 
  out what I'd do to perform similar work.  I'm sure there's a way to do it, 
  but I just can't see it.


 Hello, I would suggest defining your own data type an instance of
 monad. The sense of it would be 'sequantial IO operations which you
 can do some checks on'.

 It would have some flags and properties along with the IO computation
 itself. Operations () and (=) would construct more complex
 computations from simple ones, and since your data type is not opaque
 to you, you could inspect those complex computations for properties,
 too. Including synergetic ones, like 'this is never done, after that
 has been invoked...'

This is easier said than done.

Imagine all performActions contain their checks somehow. Let
performActionB take an argument.

  do
x - performActionA
y - performActionB x
z - performActionC
return $ calculateStuff x y z

Now performActionB and its included check depend on x. That is, the check
relies formally on the result of performActionA and thus check B must be
performed after performActionA.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] SYB with class, simplified

2007-06-25 Thread Benja Fallenstein

Hi all,

The scrap your boilerplate with class sytstem [1] has two big
advantages over the plain SYB system from Data.Generics, IMHO: One, it
lets you declare an 'open' generic function as a type class, to which
new cases can be added by adding new instances (emphasized in the
paper); and two, it lets you write recursive functions that require
other type class constraints in addition to Data (not emphasized in
the paper, but something I've frequently found myself wanting with
Data.Generics).

[1] http://homepages.cwi.nl/~ralf/syb3/

However, when trying to convert the codebase I'm working on to
SYB-with-class, I've found that the type proxies and explicit
dictionaries used to simulate type class abstraction over type classes
are... annoying. Today, I've hit on an alternative approach to
implementing SYB-with-class (YAGS, yet another generics scheme...),
with less boilerplate per generic function. The approach may or may
not be new (I haven't studied *all* of the generics proposals out
there yet); in any case, it shares the use of type-level functions
with Smash Your Boilerplate, and it uses the same underlying gfoldl
operator as SYB, but implements it in a quite different way.

I believe that the equivalent of everywhere, mkT and friends can be
implemented as type-level functions in this framework, but I haven't
actually tried it yet.

This mail is a literate script demonstrating the approach. I'm hoping
to get some feedback on the idea. :)


On to the code:


{-# OPTIONS_GHC -fglasgow-exts -fallow-overlapping-instances
-fallow-undecidable-instances #-}


Yup, we need it all...

I'll start with three example generic functions.

* 'size' calculates the number of constructors in a term, except
 for lists, for which it returns one plus sum of the element sizes.
* 'inc' increases all Ints in a term by one.
* 'prints' prints out each subterm of a term on its own line,
 except for strings, for which it prints the string,
 but not its subterms.

Thus, the following code:


test = (Hello, 7::Int, [2,3::Int])
main = do print (size test); print (inc test)
  putStrLn ; prints test; return ()


prints this:
--
11
(Hello,8,[3,4])

(Hello,7,[2,3])
Hello
7
[2,3]
2
[3]
3
[]
--

Here is the 'size' function:


class Size a where size :: a - Int

data SizeF = SizeF
instance Size a = Apply SizeF a Int where apply _ = size

instance Size a = Size [a] where size xs = 1 + sum (map size xs)
instance Apply (GMapQ SizeF) a [Int] = Size a where
size x = 1 + sum (gmapQ SizeF x)


The constraint (Apply f x r) means that 'f' is a type-level function
that, when applied to 'x,' returns 'r':


class Apply f x r | f x - r where apply :: f - x - r


Here is the 'inc' function:


class Inc a where inc :: a - a

data IncF = IncF
instance Inc a = Apply IncF a a where apply _ = inc

instance Inc Int where inc = (+1)
instance Apply (GMapT IncF) a a = Inc a where inc = gmapT IncF


And here is the 'prints' function; for illustration, the
implementation is in a slightly different style, which does without
the declaration of a new type class:


data PrintsF = PrintsF;  prints x = apply PrintsF x
instance Apply PrintsF String (IO String) where
apply _ x = print x  return x
instance (Show a, Apply (GMapM PrintsF) a (IO a)) =
 Apply PrintsF a (IO a) where
apply f x = print x  gmapM f x


Note the 'Show' constraint: 'prints' can only be applied to values all
of whose subterms implement 'Show.' This is the kind of constraint you
can't have with the standard, not-with-class SYB code.


So much for the demo code; now, onwards to the actual library. The
core consists of the following three type classes:


class Constr x   f where constr :: x - a - f a
class Param  x p f where param  :: x - f (p - a) - p - f a

class GFoldl x a f where gfoldl :: x - a - f a


Together, these classes form the equivalent of the standard SYB's
'gfoldl' method. (I'm ignoring the rest of the Data class at this
time, but I believe that it could be implemented in a similar
fashion.)

* 'Constr' and 'Param' correspond to the first and second argument
 of the standard SYB's gfoldl.

* The parameter 'x' specifies the type of fold to perform
 (GMapQ, GMapT and GMapM in the present module).

* We give an instance 'Constr' and 'Param' for each type of fold.
 We give an instance of 'GFoldl' for each type we want to fold over.

Here are the instances of GFoldl:


instance Constr x f = GFoldl x ()   f where gfoldl = constr
instance Constr x f = GFoldl x Char f where gfoldl = constr
instance Constr x f = GFoldl x Int  f where gfoldl = constr

instance (Constr x f, Param x a f, Param x [a] f) = GFoldl x [a] f where
gfoldl x [] = constr x []
gfoldl x (y:ys) = constr x (:) `p` y `p` ys where
p a b = param x a b

instance (Constr x f, Param x a f, Param x b f, Param x c f) =
 GFoldl x (a,b,c) f where

Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Benja Fallenstein

2007/6/25, Michael T. Richter [EMAIL PROTECTED]:


 OK, just to prevent this getting side-tracked: I'm absolutely
uninterested in the results of performActionA before determining if
performActionB is permitted/possible/whatever.  Think more in terms of
security permissions or resource availability/claiming than in terms of
chaining results.  I want to know before I begin to collect the results of
performAction* that I will actually stand a chance at getting results at
all.



Uh, the posts you quote were precisely about how to do that. No
side-tracking going on. :-)

All the best,
- Benja
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
Wouter Swierstra wrote:
 I don't think you really want arrows here. The right idiom is
 applicative functors (see Control.Applicative). You could then write the
 above as:
 
 calculateStuff $ x * y * z

I think you mean

 calculateStuff $ performActionA * performActionB * performActionC


Regards,
apfelmus

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


RE: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Henning Thielemann

On Mon, 25 Jun 2007, Michael T. Richter wrote:

 OK, just to prevent this getting side-tracked: I'm absolutely
 uninterested in the results of performActionA before determining if
 performActionB is permitted/possible/whatever.  Think more in terms of
 security permissions or resource availability/claiming than in terms of
 chaining results.

We have understood this.

 I want to know before I begin to collect the results of performAction*
 that I will actually stand a chance at getting results at all.

It's irrelevant, what you want. :-) In principle you can write
'performActionB x' and the monad concept urges you to handle this even if
you know, that the check that is integrated in performActionB will not
depend on x.

Wouter gave you another example which shows the problem. If there is a
monad which handles your problem, then you can write

do b - performActionA
   if b
 then performActionB
 else performActionC

You see that only one of the checks B or C can be performed, and this
depends on the result of performActionA.

Btw. I'm interested how you solve this problem in C++ in an elegant way.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
Benja Fallenstein wrote:
 Hi Peter,
 
 2007/6/25, peterv [EMAIL PROTECTED]:
 I'm baffled. So using the Arrow abstraction (which I don't know yet) would
 solve this problem? How can (perfectActionB x) be checked with without
 ever executing performActionA which evaluates to x? This can only be done
 when x is a constant expression no?
 
 Arrows separate the action -- 'performActionB' -- from the argument --
 'x', so you can look at the action before you have to compute the
 argument to it. Of course, this means that you can no longer compute
 the action from the argument -- that is, 'if x then performActionB
 else performActionC' is something you can't directly do; you have to
 use a choice primitive instead, which explicitly says use one of
 these two arrows depending on what value this argument is, which then
 lets the library check these two arrows before actually applying them
 to an argument.

Well, arrows can't solve the problem as well iff performActionB may be
permissible _depending_ on x, i.e.

  performActionB x = if x then pickFlowers else eraseHardDrive

There's no way to check whether performActionB is permissible for a
given run without executing performActionA for the permissibility of B
depends on the output of A.

But I think that Michael had conditions in mind that can be checked
before executing any of the actions. Of course, the simplest way is to
check manually:

 do
   if i'mRoot
 then do
   x - performActionA
   y - performActionB
   z - performActionC
   return $ calculateStuff x y z
 else
   cry gimme root

but you could still write performActionA somewhere without having
checked/established root permission. This can be solved by using a
custom monad

  newtype Sudo a = Sudo { act :: IO a }
   deriving (Functor,Monad,MonadIO)

which has the following operations

  performActionA :: Sudo Int
  performActionB :: Sudo String
  etc.

and that can only be run with

  sudo :: Sudo a - IO (Either String a)
  sudo m = do
b - makeMeRoot
if b
  then liftM Right $ act m
  else return $ Left Could not become Root

Putting Sudo into a module and making it abstract ensures that you can't
break the invariant that stuff of type Sudo a will either be run as
root or not at all.

Regards,
apfelmus

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Dan Mead

Micheal, I think you mean

do
 x - if .. then ..
else ..
 y - if ... then..
else...

etc etc

On 6/25/07, Michael T. Richter [EMAIL PROTECTED] wrote:


 Now I've got a situation I can't figure out how to resolve.  I want to
have a set of actions which are executed sequentially, but which, before I
even *start* to execute the first one, have been inspected for legality
and/or plausibility.  Consider this kind of sequence:

do
  x - performActionA
  y - performActionB
  z - performActionC
  return $ calculateStuff x y z

Now obviously this is going to be in a monad of some kind.  Were this a
regular, run-of-the-mill program I'd just use the IO monad.  But what I want
to do instead is, before executing any of the perform* functions, check that
the actions desired are actually *permitted* (or possible) given a set of
circumstances.  For example let's say it's a permissions issue and
performActionB can only be done if I'm root.  If I'm not root I don't want
performActionA done because I can't complete the transaction.  (Maybe
ActionA is non-reversible, say.)  Or let's say this is code that's accessing
databases on the network.  If the network link to C can't be established, I
don't want to screw around with A and B's links at all -- it's too
expensive, too time-consuming or whatever.

Were I programming this in C, C++, Python, Ruby, etc. I could do this in
my sleep.  Functions are addresses (C/C++) or objects with an ID
(Python/Ruby) so it's possible to take them and do some kind of check based
on identities before executing things (although the scaffolding around this
would be nontrivial in any of these languages except, possibly, Ruby).
Functions in Haskell don't have this property, however, so I can't figure
out what I'd do to perform similar work.  I'm sure there's a way to do it,
but I just can't see it.

  --
*Michael T. Richter* [EMAIL PROTECTED] (*GoogleTalk:*
[EMAIL PROTECTED])
*I'm not schooled in the science of human factors, but I suspect surprise
is not an element of a robust user interface. (Chip Rosenthal)*

___
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] Practical Haskell question.

2007-06-25 Thread Claus Reinke

Now I've got a situation I can't figure out how to resolve.  I want to
have a set of actions which are executed sequentially, but which, before
I even start to execute the first one, have been inspected for legality
and/or plausibility.  Consider this kind of sequence:

do
 x - performActionA
 y - performActionB
 z - performActionC
 return $ calculateStuff x y z


as has been pointed out, there is an issue as to whether the conditions
for legality can depend on runtime information. if they don't, you could
try to express the capabilities needed by each of the actions in their
types, and collect the types when composing the actions. i first saw
this trick used for type-based bytecode verification in 


   The Functions of Java Bytecode
   Mark P. Jones. In Proceedings of the OOPSLA '98 workshop on 
   Formal Underpinnings of Java, Vancouver, BC, Canada, October 1998. 
   http://web.cecs.pdx.edu/~mpj/pubs/funJava.html


but i'm sure that somewhere in the wealth of HList work, there'll be
something similar, updated for todays ghc!-)

if the conditions are static, but their validity might depend on runtime
info, you'd need to map the types expressing the capabilities required
back down to functions checking their availability, and execute those
checks before running the composed actions.

if the conditions themselves might change as actions are computed
at runtime, you might still be able to use a transaction-based approach:
only execute the actions in a sandbox at first, so that you can abandon
the transaction if any of the actions in it fail, and commit to the 
transaction (turning the sandbox changes into real changes) only if

all actions in it succeed. in a way, you're executing the transaction
twice, once only to check it will go through, then again for the actual
updates.

hth,
claus

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


[Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread apfelmus
Claus Reinke wrote:
 apfelmus wrote:
 True enough, in a sense, a dynamically typed language is like a
 statically typed language with only one type (probably several by
 distinguishing function types) and many incomplete pattern matches.
 So, you can embed a dynamically typed language into a strongly typed
 language without loosing static type checking.

 statically typed: typed at compile time
 dynamically typed: typed at runtime
 
 weakly typed: ..
 strongly typed: everything is typed and type-checked

Ah, thanks for the clear terminology.

 there are at least two problems with embedding strongly and dynamically
 typed languages into strongly and statically typed languages:
 
- it assumes that there is a globally unique static stage, entirely
separate from a globally unique dynamic stage
- it assumes that there is a unique, unchanging (closed) world of types
 
 static typing alone is too static to deal with dynamically evolving
 types or flexible ideas such as runtime compilation or dynamic linking..
 
 the solution is long-known as type Dynamic

Yes, that's what I meant. The embedding is a rather degenerate one,
making everything to be of type Dynamic.

 if you have a strongly and dynamically typed language, you can embed
 strongly and statically typed languages into it. by default, that means
 you get more type-checks than necessary and type-errors later than you'd
 wish, but you still get them. eliminating runtime type information and
 runtime type-checks in a strongly and dynamically typed language is a
 question of optimisation, similar to deforestation.

Well, you can't embed the static checks into dynamic checks without
loosing the fact that they're static. Which I think is the crucial
point: program testing can be used very effectively to show the
presence of [type] bugs but never to show their absence. To me, dynamic
typing is next to useless, i want a (partial) proof that the program
works since a proof is really the only way to know whether it works.


Regards,
apfelmus

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Michael T. Richter
On Mon, 2007-25-06 at 12:19 +0300, Benja Fallenstein wrote:

 2007/6/25, Michael T. Richter [EMAIL PROTECTED]:
 
 OK, just to prevent this getting side-tracked: I'm absolutely
 uninterested in the results of performActionA before
 determining if performActionB is permitted/possible/whatever.
 Think more in terms of security permissions or resource
 availability/claiming than in terms of chaining results.  I
 want to know before I begin to collect the results of
 performAction* that I will actually stand a chance at getting
 results at all.
 
 Uh, the posts you quote were precisely about how to do that. No
 side-tracking going on. :-)


It looked to me like there were people arguing about whether the x
returned from one action was going to be used in the next action.

Let me try and rephrase the question.  :)

A conventional approach to what I'm doing would be something like this
(in bad pseudocode):

doStuff():
if checkPossible([opA, opB, opC]):
A
B
C
else:
exception Preconditions not met

My objection to this is its error-prone scaffolding:

 1. There's no enforced link between the checking operations and the
actual operations.  By mistake or by deliberate action it is
possible to put operations in the main body which have not been
checked by the guards.
 2. As code evolves and changes, it is very easy to have the check
diverge from the contents of the body as well.


Now if the actions were trivial or easily reversible, an alternative
model is something like this (in bad pseudocode) where it's assumed that
each operation checks for its privileges/capabilities/whatever as part
of its operation:

doStuff2():
A
try:
B
try:
C
catch:
undoB
throw
catch:
undoA

This looks to me like Don Stuart's executable semi-colons and could be
coded as a pretty conventional monad (unless my eyes are deceiving me).
But if doing A, say, involved expensive operations (think: generating an
RSA key or making a database connection on a heavily-loaded server) or
if doing B involved modifying some external state that is difficult to
undo this is a less-than-ideal model.  Let's say that C fails for
whatever reason (insufficient privileges, the database server is dead,
the phase of the moon is wrong for the species of chicken sacrificed at
the keyboard -- anything), then we've got time wasted in A and B has
just changed something we can't easily unchange.

So I'd like some way of getting the automated check of
permission/capability/availability/whatever done before performing the
actual actions.

Now in a language where functions are identifiable types, a solution
could look like this (among a myriad of other possible solutions):

check(Operation):
case Operation of:
A:
return checkConditionA
B:
return checkConditionB
C:
return checkConditionC

runStuff(actions):
for each action in actions:
if not check(action.left):
throw CheckFailure
for each action in actions:
action.left(action.right)

doStuff3():
actions=[(A, a_args), (B, b_args), (C, c_args)]
try:
runStuff(actions)
catch CheckFailure:
actions=nil

The check() function called here can use the identity of the action
provided plus any information provided externally (network connections
open, permissions available, etc.) to pass/fail the
capabilities/resources/whatever and the action's execution is deferred
until the check has passed.  The action's check *AND* its execution is
unavailable to the programmer so there's less room for fraud and
oversight and all the other things which make programs buggy and
unreliable and such joys to work with both as a programmer and as a
user.  In fact with languages as malleable as Ruby (or possibly even
Python) some of the ugly scaffolding above could be made to vanish
behind the scenes leaving pretty clean code behind.  (Uglier languages
like C/C++, of course, would leave all the scaffolding lying around, but
it would still be doable.)

But of course this can't be done in Haskell this way because functions
aren't items in Haskell.  There is no function equality check.  My
check() function can't look like:

check :: (a-b)
check A = ...
check B = ...
check C = ...
check _ = error no such function

This leaves me in a position I can't think myself out of (hence the cry
for help).  I'd like it to be possible to have a do block with as little
visible scaffolding as possible (ideally none) where I can do the
equivalent of doStuff3() and runStuff() from the above pseudocode.

Now here's the tricky part

I'd ideally like to be able to do this so that it would be possible to
start with the doStuff2 implementation behind the scenes (check as you
go) and then, by changing the scaffolding behind the 

[Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread apfelmus
Michael T. Richter wrote:
 It looked to me like there were people arguing about whether the x
 returned from one action was going to be used in the next action.

 Let me try and rephrase the question.  :)

 [rephrase]

Yes, and that's an important constellation your problem description does
not consider. Take the code

 doStuff():
 if checkPossible( ?? ):
 x - A
 if x
   then B
   else C
 else:
 exception Preconditions not met

What should be put as argument into checkPossible? checkPossible([opA,
opB, opC])? What if x happens to be always true and C is never run? What
if B is possible if and only if C is not?

Sequencing actions is not just putting them in a row, but also feeding
the results of one action to the next ones. You have to restrict this in
some way to make your goal possible.

 And can it be done somehow in Haskell?

Most likely, and Haskell even tells you when your approach doesn't work
without further specification :)

Regards,
apfelmus

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


Re: [Haskell-cafe] Re: Practical Haskell question.

2007-06-25 Thread Henning Thielemann

On Mon, 25 Jun 2007, apfelmus wrote:

 Michael T. Richter wrote:
  It looked to me like there were people arguing about whether the x
  returned from one action was going to be used in the next action.
 
  Let me try and rephrase the question.  :)
 
  [rephrase]

 Yes, and that's an important constellation your problem description does
 not consider.

If Michael had asked for code that has to be executed _after_ the actual
actions, say for cleanup, this would have been simple. If he knows that
the performAction commands don't use results of former actions, then the
Applicative approach described earlier in this thread would work, though
without 'do' notation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Simon Peyton-Jones
The intention is that it should be straightforward to suppress warnings.

Warning about defaulting is important, because it's a place where a silent 
choice affects the dynamic semantics of your program.  You can suppress the 
warning by supplying a type signature.  In your example:

|  main =
| let r = pi :: Double
| x = r ^ (3 :: Int)
| y = r ^ 3
| z = r Prelude.^ 3
| in  putStrLn $ show (x,y,z)

Simply add a type signature for 'z', or for the naked 3 in z's definition.

I think it matters what type is chosen, because it affects the output of the 
program; it's good practice to be explicit about what type you want, at each 
site where defaulting is applied.  If your idea of good practice differs from 
mine, then you can record your choice by using -fno-warn-type-defaults.

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


[Haskell-cafe] Re: FFI and Excel VBA

2007-06-25 Thread Simon Marlow

We don't recommend calling shutdownHaskell() from DllMain().  Some information 
here:

http://haskell.org/haskellwiki/GHC/Using_the_FFI#Debugging_Haskell_DLLs

It should be safe to call shutdownHaskell() (aka hs_exit()) *before* unloading a 
DLL, and before exiting the program.


Cheers,
Simon

Lennart Augustsson wrote:

There is a number of problems, I'm not sure which one you are encountering.
Here are some that I remember:

The sample C code doesn't shut down the ghc runtime properly when the  
DLL is unloaded.  This causes  a timer interrupt to jump into the void.  
This is easily fixed with a couple of more lines of C.


The ghc runtime installs handlers for various things that it shouldn't 
touch when used as a DLL.


  -- Lennart

On 6/19/07, *Lewis-Sandy, Darrell * [EMAIL PROTECTED] 
mailto:[EMAIL PROTECTED] wrote:


I am new to using the Haskell FFI, and have been trying to implement
the example in section 11.6 of the GHC user's guide. 

 


I have finally gotten to the point where my dll compiles (there is a
missing space in the mainDll.h code at line 4:12) using GHC 6.6.1,
and used the declare statement to expose the adder function in
Excel VBA.  My VBA Code is given below:

 


Private Declare Function adder Lib  adder.dll Alias [EMAIL PROTECTED]
(ByVal x As Integer, ByVal y As Integer) As Integer

 


Private Sub test()

Debug.Print adder(1, 2)

End Sub

 

 

 


*My problem is this:*

The function works fine (the immediate window displays 3), but when
I terminate Excel, I get an application error (The instruction at …
referenced memory at … . The memory could not be read.).  Does
anyone else have any experience calling Haskell from VBA that might
be relevant?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org mailto: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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Bulat Ziganshin
Hello Michael,

Monday, June 25, 2007, 2:10:28 PM, you wrote:
 Does this make more sense now?  And can it be done somehow in Haskell?

runCheckedCode = checkBeforeRun [actionA x y, actionB z t, actionC]

actionA x y b | b = -- check conditions
  | otherwise = -- perform action

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] problem implementing an EDSL in Haskell

2007-06-25 Thread Daniil Elovkov

Hi Conal

2007/6/24, Conal Elliott [EMAIL PROTECTED]:

By embedded DSL, we usually mean identifying meta-language (Haskell)
expressions with object language (DSL) expressions, rather than having an
Exp data type.  Then you just use meta-language variables as
object-language variables.  The new data types you introduce are then
domain-oriented rather than language-oriented.  Is there a reason that this
kind of embedded approach doesn't work for you?


Hmm, sorry, I must admit I didn't quite get it.

However, in the situation I described, I don't just have an Exp data
type, rather have it (and probably some other data types) typeful.
Which lets me leverage the meta-language's (Haskell's) typing rules to
enforce correctness of my DS language's expression correctness.

I absolutely didn't want to make an accent on embedded. Sorry, if
that introduced some confusion. And that's not important or principal
to me, it's just how I called it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Question about HList possibilities

2007-06-25 Thread Scott West

Hello all,

Given an HList (http://homepages.cwi.nl/~ralf/HList/) would it be
possible to do the following:

Create a class/function/magicks that would essentially do what
hOccursMany does, except it would not return a list of elements, but a
new HList. For example, would this allow us to be able to write more
lax typing constraints and say extract only things that are in lists.

ie) HCons hi  (HCons [2.2,3.3] (HCons 'a' hNil)) - HCons hi
(HCons [2.2,3.3]  hNil)

(removing the Char element).

I tried to write something like this but I did not get very far, is it
even possible? I'm new to this type-level programming :)

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 25, 2007, at 4:48 AM, Simon Peyton-Jones wrote:

The intention is that it should be straightforward to suppress  
warnings.


Simply add a type signature for 'z', or for the naked 3 in z's  
definition.


I constructed my example from larger modules peppered with small  
integer constants; such signatures would become a significant  
percentage of the code. I was hoping for a solution whose code size  
is at worst linear in the number of distinct integer constants used,  
not the number of times they are used. I'd like to avoid redefining  
operators if I can help it.


Given that there are entire languages in common use that don't  
support Integer, I don't see why ghc -Wall -Werror can't become  
such a language when it sees



default (Int)


Instead it issues defaulting warnings even in the presence of this  
declaration.


I couldn't find a way to add a type signature once for each small  
integer constant I plan to use; it would appear to me that



2,3 :: Int


by itself is not legal Haskell. The best I can do is to instead write


i2,i3 :: Int
(i2,i3) = (2,3)


which imposes a per-use penalty of one character per use, and is less  
readable than simply unrolling the constants in each use. In other  
words, if I can't write x^3, I find x*x*x more transparent than x^i3  
or x^(3::Int).


Despite my participation in a broader discussion, my hope in starting  
this thread was to understand how to most elegantly use the specific  
programming language ghc -Wall -Werror.


It continues to appear to me that ghc -Wall -Werror doesn't support  
small Int constants without a per-use penalty, measured in code length.


On Jun 25, 2007, at 4:48 AM, Simon Peyton-Jones wrote:
I think it matters what type is chosen, because it affects the  
output of the program; it's good practice to be explicit about what  
type you want, at each site where defaulting is applied.


I agree, so I'm glad I asked here rather than reporting warnings in  
the presence of default (Int) as a bug.


Unless I misunderstand and it is already possible, I'd now prefer a  
language extension that allows the explicit declarations



2,3 :: Int


once for each affected numeric literal.

 
___

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


RE: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Simon Peyton-Jones
| Unless I misunderstand and it is already possible, I'd now prefer a
| language extension that allows the explicit declarations
|
|  2,3 :: Int
|
| once for each affected numeric literal.

i2 = 2 :: Int
i3 = 3 :: Int

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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Jon Cast
On Monday 25 June 2007, Michael T. Richter wrote:
 On Mon, 2007-25-06 at 01:05 -0500, Jon Cast wrote:
  What exactly are you trying to do?

 I'm trying to model a transactional system which could fail
 mid-transaction without an easy rollback on conditions which could be
 checked in advance.

snip

 Now if I could just check permissions on each operation 
 the monad emerging is clearer.  Each call in the do block to C, then D
 and finally E would be individually checked for permissions in the Monad
 before the next step could progress.  I can do this.  But if I want to
 change the model to pre-check the privileges (because of performance
 issues or because of resource allocation issues or whatever) I see no
 easy way to do the same thing.  This intrigues me.

Why?  There's no easy or simple way to tell what operations you're going to 
execute in advance.  Take a concrete example:

do
  s - readFile /etc/ourProg
  let Right xn = flip parse s $ many $ fileName
  flip mapM xn $ \ filename - readFile xn

Now, you can't possible pre-check this for permissions, because the argument 
to readFile in the fourth line is drawn from an external file; you would have 
to check for permission to read every file in the world.

If your particular permissions issues are indeed independent of the arguments 
to performB, you can use an arrow:

data MyArrow alpha beta = MyArrow (IO Bool) (alpha - IO beta)
instance Arrow MyArrow where
  arr f = MyArrow (return True) (return . f)
  MyArrow c0 a0  MyArrow c1 a1
 = MyArrow (liftM2 () c0 c1) (\ x - a0 x = a1)

Then you can check the pre-conditions beforehand.  (If you want to see why 
using an arrow helps, try implementing an instance of the class

class Arrow a = ArrowApply a where
  apply :: a (a alpha beta, alpha) beta

for MyArrow.  Can't be done, but apply is built in to monads).

Sincerely,
Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer

On Jun 25, 2007, at 8:15 AM, Simon Peyton-Jones wrote:


i2 = 2 :: Int
i3 = 3 :: Int


The code


{-# OPTIONS_GHC -Wall -Werror #-}

module Main where

i2 = 2 :: Int
i3 = 3 :: Int

main :: IO ()
main = putStrLn $ show (i2,i3)


generates the errors


Main.hs:5:0: Warning: Definition but no type signature for `i2'
Main.hs:6:0: Warning: Definition but no type signature for `i3'


and imposes a linear per-use penalty of one extra character per use.  
If I can't write x^3, I find x*x*x more transparent than x^i3.


I know how to fix this; my previous message considered


i2,i3 :: Int
(i2,i3) = (2,3)


which still imposes a linear per-use penalty of one extra character  
per use.


It continues to appear to me that ghc -Wall -Werror doesn't support  
small Int constants without a per-use penalty, measured in code length.


Am I the only one blessed/cursed with a vision of how proponents of  
practical languages would have a field day with this? Perhaps I'm  
reading too many blogs.


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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Arie Peterson
As others have explained, you can't analyse your do-constructs, because
functions are opaque -- at the value level.

The canonical option would indeed seem to be to use arrows (or applicative
functors), instead of monads.

--

If you want to stick to monads, there is another possibility: carry around
the necessary checks *at the type level*. Below is a sketch of how you
could do this.

Things to note:

- Uses HList http://homepages.cwi.nl/~ralf/HList/.

- Deciding which checks to perform happens statically, so it will check
for any actions that are mentioned, even if they are not actually
performed:

  actionX = \ b - if b then actionY else actionZ

will perform checks necessary for actionZ, even if actionX happens to
return True.

- First draft; may contain sharp edges (or outright errors). There are
some possibilities for generalisation: e.g. do it over an arbitrary monad,
instead of IO.

--8--

module CheckIO where


import Control.Monad.Error
import HList
  (
(:*:)
  , (.*.)
  , HNil
  (
HNil
  )
  , HOccurs
  )


data CheckIO labels x
  = CheckIO (IO x)

instance Monad (CheckIO l) where
  return = CheckIO . return
  (CheckIO a) = h = CheckIO $ a = ((\ (CheckIO x) - x) . h)
  fail = CheckIO . fail

instance Functor (CheckIO l) where
  fmap f (CheckIO a) = CheckIO (fmap f a)

withCheck :: (HOccurs label labels) = IO x - label - CheckIO labels x
withCheck = flip (const CheckIO)


class Check label where
  check :: label - ErrorT String IO () -- |label| argument is for type
inference only

class Checks c where
  performChecks :: c - ErrorT String IO () -- |c| argument is for type
inference only

instance Checks HNil where
  performChecks _ = return ()

instance (Check label,Checks rest) = Checks (label :*: rest) where
  performChecks _ = check (undefined :: label)  performChecks (undefined
:: rest)

runWithChecks :: forall labels x. (Checks labels) = CheckIO labels x -
labels - ErrorT String IO x
runWithChecks (CheckIO q) _ = performChecks (undefined :: labels)  liftIO q

-- End of general CheckIO code; the following example use would actually
go in a different module.

-- Component actions

data Root
  = Root

instance Check Root where
  check _ = do
liftIO $ putStrLn Root privileges required. Enter root password:
pw - liftIO getLine
if pw == myRootPassword
  then return ()
  else throwError No root.

actionA :: (HOccurs Root labels) = CheckIO labels ()
actionA = putStrLn Enter a string: `withCheck` Root


data Database
  = Database

instance Check Database where
  check _ = liftIO $ putStrLn Database is ok.

actionB :: (HOccurs Database labels) = CheckIO labels String
actionB = getLine `withCheck` Database


data Connection
  = Connection

instance Check Connection where
  check _ = do
liftIO $ putStrLn Connection up?
x - liftIO getLine
if x == yes
  then return ()
  else throwError No connection.

actionC :: (HOccurs Connection labels) = String - CheckIO labels ()
actionC x = putStrLn (reverse x) `withCheck` Connection

-- Composed action

main :: ErrorT String IO ()
main = action `runWithChecks` (Connection .*. Database .*. Root .*. HNil)

action :: (HOccurs Root labels,HOccurs Connection labels,HOccurs Database
labels) = CheckIO labels ()
action = do
  actionA
  x - actionB
  actionC x

--8--


Kind regards,

Arie

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


Re: [Haskell-cafe] Haskell version of ray tracer code is much slower than the original ML

2007-06-25 Thread Spencer Janssen
On Thu, 21 Jun 2007 11:55:04 +0100
Philip Armstrong [EMAIL PROTECTED] wrote:

 In odd spare moments, I took John Harrops simple ray tracer[1]  made
 a Haskell version:
 
   http://www.kantaka.co.uk/cgi-bin/darcsweb.cgi?r=ray
 
   darcs get http://www.kantaka.co.uk/darcs/ray
 
 It's pretty much a straight translation into idiomatic Haskell (as far
 as my Haskell is idiomatic anyway).
 
 Unfortunately, it's a lot slower than the ML version, despite turning
 all the optimisation options up as far as they'll go. Profiling
 suggests that much of the time is spent in the intersection' function,
 and that the code is creating (and garbage collecting) an awful lot of
 (-|) vector subtraction thunks. Trying to make intersection' or
 ray_sphere stricter (with seq) appears to have no effect whatsoever:
 the output of -ddump-simpl is unchanged (with the arguments all
 staying lazy).
 
 Am I missing anything obvious? I don't want to carry out herculean
 code rewriting efforts: that wouldn't really be in the spirit of the
 thing.
 
 cheers, Phil
 
 [1] http://www.ffconsultancy.com/languages/ray_tracer/comparison.html
 

With a very minor change (attached), your Haskell ray tracer runs faster
than the OCaml version on my machine.  There's a bug GHC where it does
not recognize -fexcess-precision at the command line, but an
OPTIONS_GHC pragma does work correctly.  This flag brings runtime from
about 60s to 20s on my machine (Core Duo 1.83GHz) -- compared to 25s
for the OCaml version.

Results (each run twice to avoid OS buffering of the executable):

% uname -a
Linux localhost 2.6.22-rc4 #5 SMP Tue Jun 19 17:29:36 CDT 2007 i686
Genuine Intel(R) CPU T2400 @ 1.83GHz GenuineIntel GNU/Linux
% ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6
% ocamlopt -version
3.09.3
% (time ./hsray) | md5sum
./hsray  20.23s user 0.03s system 98% cpu 20.536 total
63a359e5c388f2004726d83d4337f56b  -
% (time ./hsray) | md5sum
./hsray  19.74s user 0.07s system 99% cpu 19.907 total
63a359e5c388f2004726d83d4337f56b  -
% (time ./mlray) | md5sum  
./mlray  25.55s user 0.00s system 98% cpu 25.831 total
63a359e5c388f2004726d83d4337f56b  -
% (time ./mlray) | md5sum
./mlray  25.63s user 0.04s system 98% cpu 25.981 total
63a359e5c388f2004726d83d4337f56b  -


Cheers,
Spencer Janssen

ray_pragma.dpatch
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Derek Elkins
On Sun, 2007-06-24 at 13:33 +0100, Claus Reinke wrote:

 if you have a strongly and dynamically typed language, you can embed
 strongly and statically typed languages into it. by default, that means
 you get more type-checks than necessary and type-errors later than 
 you'd wish, but you still get them.

Are you sure this is true in a meaningful way?  You can always simply
run the type checker at run-time, and this is indeed where statically
typed languages are heading, but e.g. phantom types, and runST style
tricks are areas where the embedding into a dynamically typed language
is, at the very least, not trivial.



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


Re: [Haskell-cafe] Practical Haskell question.

2007-06-25 Thread Arie Peterson
I wrote:

 If you want to stick to monads, there is another possibility: carry around
 the necessary checks *at the type level*. Below is a sketch of how you
 could do this.

Importantly, the given code still requires you to specify the checks by
hand, when running the action; it only checks that you didn't forget a
necessary check.

Perhaps someone can improve this, so it derives the necessary checks
automatically?


Greetings,

Arie

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


Re: [Haskell-cafe] Question about HList possibilities

2007-06-25 Thread Jeff Polakow
Hello,

 Hello all,
 
 Given an HList (http://homepages.cwi.nl/~ralf/HList/) would it be
 possible to do the following:
 
 Create a class/function/magicks that would essentially do what
 hOccursMany does, except it would not return a list of elements, but a
 new HList. For example, would this allow us to be able to write more
 lax typing constraints and say extract only things that are in lists.
 
 ie) HCons hi  (HCons [2.2,3.3] (HCons 'a' hNil)) - HCons hi
 (HCons [2.2,3.3]  hNil)
 
 (removing the Char element).
 
 I tried to write something like this but I did not get very far, is it
 even possible? I'm new to this type-level programming :)
 
One approach is to write a HList filter function. You need to use 
type-level bools, type-level apply, and break up the filter function into 
two parts; you need a second typeclass to discriminate on the HBool which 
results from applying your predicate to each element of the HList.

Below is some code that works for me.

-Jeff

-

{-# OPTIONS -fglasgow-exts 
-fallow-undecidable-instances 
-fallow-overlapping-instances 
#-}


module MyHList where

class TypeCast   a b   | a - b, b-a   where typeCast   :: a - b
class TypeCast'  t a b | t a - b, t b - a where typeCast'  :: t-a-b
class TypeCast'' t a b | t a - b, t b - a where typeCast'' :: t-a-b
instance TypeCast'  () a b = TypeCast a b where typeCast x = typeCast' () 
x
instance TypeCast'' t a b = TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x


data HNil = HNil deriving (Show, Read, Eq)
data HCons e l = HCons e l deriving (Show, Read, Eq)


data HTrue = HTrue deriving (Eq, Show)
data HFalse = HFalse deriving (Eq, Show)


class HApply f e v | f e - v
where hApply :: f - e - v


-- This HFilter uses an accumulator to avoid using typecast.
--
class HFilter acc p l l' | acc p l - l'
where hFilter :: acc - p - l - l'
instance HFilter acc p HNil acc
where hFilter acc _ _ = acc
instance (HApply p x b, HFilter1 b x acc p xs xs') = HFilter acc p (HCons 
x xs) xs'
where hFilter acc p (HCons x xs) = hFilter1 (hApply p x) x acc p xs

class HFilter1 b x acc p xs xs' | b x acc p xs - xs'
where hFilter1 :: b - x - acc - p - xs - xs'
instance HFilter acc p xs xs' = HFilter1 HFalse x acc p xs xs'
where hFilter1 _ _ acc p xs = hFilter acc p xs
instance HFilter (HCons x acc) p xs xs' = HFilter1 HTrue x acc p xs xs'
where hFilter1 _ x acc p xs = hFilter (HCons x acc) p xs


-- Here is a specific type-level function to check if something is a list.
-- Can't avoid the typeCast here because of functional dependencies on 
HApply
--
data IsList = IsList
instance HApply IsList [a] HTrue
where hApply _ _ = undefined
instance TypeCast HFalse b = HApply (IsList) a b
where hApply _ _ = undefined


test = hFilter HNil IsList $ HCons hi  (HCons [2.2,3.3] (HCons 'a' 
HNil))






---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Jaap Weel
 I've been going over my code trying to get it all to compile with
 ghc -Wall -Werror

I recently ran across what may be a good reason not to use -Wall in
combination with -Werror (and similar combinations in other
compilers), at least not as the standard build switches for software
you intend to distribute. It causes bitrot, because -Wall will in the
future turn on warnings that don't even exist yet today, and -Werror
will turn those warnings into errors. The upshot is that you can write
code that entirely follows the standard that defines whatever language
you're using (e.g. Haskell 98), and still have it break in the future,
even if future compilers adhere to the standard. If you are serious
about writing portable and durable code, you may want to avoid this.

(I ran into this problem while trying to resurrect an excellent but
unmaintained compiler written in lots of OCaml and a little C. Both
ocaml and gcc have grown many new warnings in the last few years.)

--

  /jaap


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


[Haskell-cafe] Tools for Haskell and COM

2007-06-25 Thread Lewis-Sandy, Darrell
Are there any currently maintained tools for interfacing Haskell with COM
objects?   It appears that both Haskell script and Haskell direct haven't
been updated since the turn of the century, and have fallen out of step with
recent library changes.  

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


Re: [Haskell-cafe] Re: Best idiom for avoiding Defaulting warningswith ghc -Wall -Werror ??

2007-06-25 Thread Claus Reinke

if you have a strongly and dynamically typed language, you can embed
strongly and statically typed languages into it. by default, that means
you get more type-checks than necessary and type-errors later than 
you'd wish, but you still get them.


Are you sure this is true in a meaningful way?  You can always simply
run the type checker at run-time, and this is indeed where statically
typed languages are heading, but e.g. phantom types, and runST style
tricks are areas where the embedding into a dynamically typed language
is, at the very least, not trivial.


true, meaningful, yes; you'd still not be able to access ST references in 
the wrong thread, but in a purely dynamically typed language, you will 
only find out about problems in that area while the thread is already in 
the middle of its run. runST alone does not give transaction semantics.


but it is also true that being able to isolate whole sub-programs at 
once, so that their type-checks are done before they are being run, 
and no type-checks are done while those sub-programs are run, is 
more than just an optimisation. it is a question of being able to express

certain type-check-level transaction constraints: either the whole
sub-program can be shown to run without type-errors or no part 
of the sub-program is permitted to run. (being able to fit a whole

program into a single such type-level transaction is a special case,
which we call static typing)

see also apfelmus' message, which raised the same point, and my
reply. that exchange reminded me that dynamic/typecase is not
only a necessary addition to otherwise static typing, but also enables
a very desirable addition to otherwise dynamic typing. the idea being
that by default, all typing should be static, unless explicitly specified 
otherwise by use of dynamic/typecase. in other words, dynamic
typing has to be made explicit, and is only used were static typing 
is not expressive enough; the majority of code consists of statically

typed fragments enjoying the type-level transaction property; entry
into such a fragment is protected by a dynamic type check, exit
from such a fragment might reconstruct dynamic type information.

claus

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Ian Lynagh
On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:
 
z = r Prelude.^ 3

I don't know if (^) in particular is what is causing you problems, but
IMO it has the wrong type; just as we have
(!!) :: [a] - Int - a
genericIndex :: (Integral b) = [a] - b   - a
we should also have
(^)  :: (Num a) = a - Int - a
genericPower :: (Num a, Integral b) = a - b   - a
(or some other function name).

I've mentioned this before, but until
http://hackage.haskell.org/trac/haskell-prime/ticket/118
is resolved we don't know where to discuss it (the haskell-prime or
libraries list).


Incidentally, I am another person who wants to be warned when defaulting
happens because I don't want to actually use defaulting, but I would
have no objection to the warning being suppressed if someone has
explicitly given a default declaration (and thus, presumably, does
want to use defaulting).


Thanks
Ian

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


Re: [Haskell-cafe] Parallel + exceptions

2007-06-25 Thread Andrew Coppin

Felipe Almeida Lessa wrote:

On 6/23/07, Andrew Coppin [EMAIL PROTECTED] wrote:

It's nice that you can have millions of threads if you want to do
something very concurrent. What I tend to want is parallel - doing
stuff that *could* be done in a single thread, but I want it to go
faster using my big mighty multicore box. As I understand it, you have
to do something special to make that happen...?


Have you seen this paper?
http://www.macs.hw.ac.uk/~dsg/gph/papers/html/Strategies/strategies.html

It's probably want you want, I think.



Well, it certainly looks interesting... thanks.

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


Re: [Haskell-cafe] Collections

2007-06-25 Thread Andrew Coppin

Lennart Augustsson wrote:
If you don't run into graphs you are either solving very peculiar 
problems, or you don't recognize them when you see them.  They are 
everywhere.


I see lots of *trees*, but no general graphs. (As in, *data* structures 
having cycles in them. My *code* is often cyclic...)


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread David Roundy
On Mon, Jun 25, 2007 at 07:31:09PM +0100, Ian Lynagh wrote:
 I don't know if (^) in particular is what is causing you problems, but
 IMO it has the wrong type; just as we have
 (!!) :: [a] - Int - a
 genericIndex :: (Integral b) = [a] - b   - a
 we should also have
 (^)  :: (Num a) = a - Int - a
 genericPower :: (Num a, Integral b) = a - b   - a
 (or some other function name).
 
 I've mentioned this before, but until
 http://hackage.haskell.org/trac/haskell-prime/ticket/118
 is resolved we don't know where to discuss it (the haskell-prime or
 libraries list).

That would be great!
-- 
David Roundy
Department of Physics
Oregon State University
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Plugin Problem - Weirder

2007-06-25 Thread Andrea Rossato
On Fri, Jun 22, 2007 at 03:32:19PM +0200, Daniel Fischer wrote:
 Am Freitag, 22. Juni 2007 04:29 schrieb Donald Bruce Stewart:
 
  The file system was down here, sorry.  Should be up now.
 
 Ah, just unlucky timing.
 darcs got, installed, all well.


I Know I'm probably late, but with the darcs ource I keep getting:

[ 6 of 22] Compiling System.Plugins.Consts (
src/System/Plugins/Consts.hs, dist/build/System/Plugins/Consts.o )

src/System/Plugins/Consts.hs:32:60:
lexical error in string/character literal at character '\ESC'

Am I missing something?

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


[Haskell-cafe] Re: Collections

2007-06-25 Thread apfelmus
Andrew Coppin wrote:
 Lennart Augustsson wrote:
 If you don't run into graphs you are either solving very peculiar
 problems, or you don't recognize them when you see them.  They are
 everywhere.
 
 I see lots of *trees*, but no general graphs. (As in, *data* structures
 having cycles in them. My *code* is often cyclic...)

So what does a compiler do to typecheck it? It represents your code as a
graph and calculates strongly connected components.

Regards,
apfelmus

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Chad Scherrer

Bryan,

I downloaded your FileManip library and Duncan's zlib library, but I
kept getting a Too many open files exception (it matches over 9000
files). I tried to get around this using unsafeInterleaveIO as Greg
had suggested, so now I have this:

foo = namesMatching */*.z =
 fmap B.concat . mapM (unsafeInterleaveIO . fmap decompress . B.readFile)

Now it doesn't complain about too many open files, but instead I get
this runtime error:

LPS *** Exception: user error (Codec.Compression.Zlib: incorrect header check)

I tried to get the same error on simpler code, and I've found this
gives the same error:

bar = fmap decompress $ L.readFile myData.z

It seemed to me the file might be corrupted, but I can do
gunzip -c  myData.gz

at the command line and see the results just fine.

I also tried gzipping a different, smaller file, and I changed the
string in bar accordingly. No error in that case. So it seems to be
a problem with myData.z, but why would it gunzip from the command line
with no trouble in that case?

Thanks,
Chad

On 6/24/07, Bryan O'Sullivan [EMAIL PROTECTED] wrote:

Using my FileManip library, you'd do that like this.

import Codec.Compression.GZip
import qualified Data.ByteString.Lazy as B
import System.FilePath.Glob

foo :: IO B.ByteString
foo = namesMatching */*.gz =
   fmap B.concat . mapM (fmap decompress . B.readFile)

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/FileManip-0.2

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


Re: [Haskell-cafe] Re: Collections

2007-06-25 Thread Andrew Coppin

apfelmus wrote:

Andrew Coppin wrote:
  

I see lots of *trees*, but no general graphs. (As in, *data* structures
having cycles in them. My *code* is often cyclic...)



So what does a compiler do to typecheck it? It represents your code as a
graph and calculates strongly connected components.
  


That's quite true - but *I* am not writing a compiler, am I? ;-)

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


Re: [Haskell-cafe] Parallel + exceptions

2007-06-25 Thread Andrew Coppin

Andrew Coppin wrote:

Felipe Almeida Lessa wrote:

Have you seen this paper?
http://www.macs.hw.ac.uk/~dsg/gph/papers/html/Strategies/strategies.html

It's probably want you want, I think.



Well, it certainly looks interesting... thanks.


Does anybody know where I can find a version of this paper that actually 
has the diagrams in it?


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


Re: [Haskell-cafe] Collections

2007-06-25 Thread Thomas Schilling

On 25 jun 2007, at 20.38, Andrew Coppin wrote:


Lennart Augustsson wrote:
If you don't run into graphs you are either solving very peculiar  
problems, or you don't recognize them when you see them.  They are  
everywhere.


I see lots of *trees*, but no general graphs. (As in, *data*  
structures having cycles in them. My *code* is often cyclic...)


Graphs may appear as infinity trees, you know.

data Tree = L Int | B Tree Tree deriving Show

t1 = B (L 42) (B (L 23) t1)

= B (L 42) (B (L 23) (B (L 42) (B (L 23) (B (L 42) (B (L 23) (B (L  
42) ...

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Dave Bayer


On Mon, Jun 25, 2007 at 07:31:09PM +0100, Ian Lynagh wrote:


I don't know if (^) in particular is what is causing you problems, but
IMO it has the wrong type; just as we have
(!!) :: [a] - Int - a
genericIndex :: (Integral b) = [a] - b   - a
we should also have
(^)  :: (Num a) = a - Int - a
genericPower :: (Num a, Integral b) = a - b   - a


On Jun 25, 2007, at 11:40 AM, David Roundy wrote:


That would be great!


Ahh, a consensus I can enthusiastically support.

It would seem to me a good library design rule of thumb to make ANY  
argument that will be counted down to zero by simple recursion an  
Int, with the type of (^) a standard application of this general  
principle.


Even with strict evaluation and tail recursion, if I want to write  
something that's going to need more than 2^31 iterations, I want the  
compiler to make me jump through hoops to say so. With the current  
type for (^), I'm jumping through hoops to say something that I can  
more easily unroll by hand.


Your proposal for (^) would allow genericPower to use the  
asymptotically faster algorithm of writing out the exponent in binary  
and multiplying together repeated squares, leaving the simple  
recursion to (^).

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


[Haskell-cafe] runInteractiveProcess leaks memory, runInteractiveCommand does not

2007-06-25 Thread Andrea Rossato
Hi,

after many test I found out that System.Process.runInteractiveProcess
leaks memory while runInteractiveCommand does.

The issue of memory leaks related to running external program was
raised here:
http://www.haskell.org/pipermail/haskell-cafe/2007-June/027234.html
and Bryan noted that after a while the process hits a steady state:
http://www.haskell.org/pipermail/haskell-cafe/2007-June/027278.html

This is true for runInteractiveCommand, but not for
runInceractiveProcess, even though, both relay on the same foreign C
imported function.

I think this is a ghc bug, but before reporting it I'd like to have
someone to confirm it.

I wrote this code that demonstrate my point. Could you please have a
look?

Thanks for you kind attention.

Andrea

here's the code.:

module Main where

import System.Process
import System.Posix.IO
import System.IO
import Control.Concurrent

readOutput rh =
do str - hGetLine rh
   return str

runWith c f = 
 do (i,o,e,p) - f c
exit - waitForProcess p
str - readOutput o
putStrLn str
cHandles i o e
threadDelay $ 10 * 1
runWith c f 

runRunIntProcess c =
do (inp,out,err,p) - runInteractiveProcess c [] Nothing Nothing
   return (inp,out,err,p)

runRunIntCommand c =
do (inp,out,err,p) - runInteractiveCommand c
   return (inp,out,err,p)

cHandles i o e =
do hClose i
   hClose o
   hClose e


-- this does not leaks
-- this reaches a steady state after a while:
--virt
--5528 3404  668 S  6.6  0.7  13:07.48 procRunInComm

main = runWith date runRunIntProcess


-- this keep on growing
--10548 8436  676 S  8.6  1.6  13:15.24 procRunInProc

main' = runWith date runRunIntCommand

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Chaddaï Fouché

I also tried gzipping a different, smaller file, and I changed the
string in bar accordingly. No error in that case. So it seems to be
a problem with myData.z, but why would it gunzip from the command line
with no trouble in that case?

Thanks,
Chad


Because gunzip is smarter than your program in that he can decompress
gzip format but Z format too (which is produced by the very old
compress unix utility).

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


Re: [Haskell-cafe] Parallel + exceptions

2007-06-25 Thread Andrew Coppin

Sebastian Sylvan wrote:

On 25/06/07, Andrew Coppin [EMAIL PROTECTED] wrote:

Does anybody know where I can find a version of this paper that actually
has the diagrams in it?



http://citeseer.ist.psu.edu/cache/papers/cs/8487/http:zSzzSzwww.cee.hw.ac.ukzSz~dsgzSzgphzSzpaperszSzabstractszSz..zSzpszSzstrategies.pdf/trinder98algorithm.pdf 


Thanks! :-)

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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Henning Thielemann

On Mon, 25 Jun 2007, Ian Lynagh wrote:

 On Fri, Jun 22, 2007 at 11:37:15AM -0700, Dave Bayer wrote:
 
 z = r Prelude.^ 3

 I don't know if (^) in particular is what is causing you problems, but
 IMO it has the wrong type; just as we have
 (!!) :: [a] - Int - a
 genericIndex :: (Integral b) = [a] - b   - a
 we should also have
 (^)  :: (Num a) = a - Int - a
 genericPower :: (Num a, Integral b) = a - b   - a
 (or some other function name).

Seconded!

 I've mentioned this before, but until
 http://hackage.haskell.org/trac/haskell-prime/ticket/118
 is resolved we don't know where to discuss it (the haskell-prime or
 libraries list).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Propositional logic question

2007-06-25 Thread Dave Tapley

Hopefully this is just about on topic enough..
(Oh and it's not home work, I just can't bring myself to let it go!)

Taken from Simon Thompson: Type Theory and Functional Programming

Section 1.1
Exercise 1.3

Question: Give a proof of (A = (B = C)) = ((A /\ B) = C).

Now I can easily perform (and verify, it's given earlier in the
section) the proof of implication with the terms flipped around:
((A /\ B) = C) = (A = (B = C))
Thus:

[A]2  [B]1
--- (/\ I)  [(A /\ B) = C]3
 A /\ B
 (= E)
  C
- (= I) 1
B = C
-- (= I) 2
A = (B = C)
--- (= I) 3
((A /\ B) = C) = (A = (B = C))


My problem arrives finding a solution to the exercise question, my
approach is to basically run the above proof backwards.
Thus:

A = (B = C) A
- (= E) B
 B = C
- (= E)
  C

Now at this point I thought aha, I can use (= I) to introduce (A /\
B) and get:

- (= I) 1
   (A /\ B) = C

But here I am only entitled to discharge (A /\ B) in the preceding
proof and not A and B on their own.
What proof which would allow me to discharge my assumptions A and B?

I can see in my head how it makes perfect sense, but can't jiggle a
way to do it using only the given derivations.

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


Re[2]: [Haskell-cafe] directory tree?

2007-06-25 Thread Bulat Ziganshin
Hello Chad,

Monday, June 25, 2007, 10:47:11 PM, you wrote:

 bar = fmap decompress $ B.readFile myData.gz

try it with non-lazy bytestrings:

import qualified Data.ByteString as B


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Chad Scherrer

Jedaï,

Are you sure you're not confusing .z with .Z?

http://kb.iu.edu/data/afcc.html

And is it possible that gzip is smarter somehow? Doesn't
Codec.Compression.GZip call the same C library used by gzip?

Chad

On 6/25/07, Chaddaï Fouché [EMAIL PROTECTED] wrote:

Because gunzip is smarter than your program in that he can decompress
gzip format but Z format too (which is produced by the very old
compress unix utility).

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


Re: [Haskell-cafe] Propositional logic question

2007-06-25 Thread Jeff Polakow
Hello,

 But here I am only entitled to discharge (A /\ B) in the preceding
 proof and not A and B on their own.
 What proof which would allow me to discharge my assumptions A and B?
 
 I can see in my head how it makes perfect sense, but can't jiggle a
 way to do it using only the given derivations.
 
You have (A /\ B) to work with. Remember that intuitionistic/classical 
logic places no restrictions on how many times you use each hypothesis.

hth,
  Jeff


---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Propositional logic question

2007-06-25 Thread Dave Tapley

Whoops, okay after two lines (thanks to oerjan) on #haskell I realise
that yes, it is as easy as it should have been.

For completeness:

[A /\ B]1
 (/\ E1)  [A = (B = C)]2
 A
- (= E)
  B = C
[A /\ B]1
 (/\ E2)
 B  B = C
- (= E)
C
-- (= I)1
(A /\ B) = C

 (= I)2
(A = (B = C)) = ((A /\ B) = C)


Learning is fun :)

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


Re: Re[2]: [Haskell-cafe] directory tree?

2007-06-25 Thread Chad Scherrer

Bulat,

I don't think I can. (1) (de)compress is defined for lazy bytestrings,
and (2) my data comes to me compressed in order to fit it all on a
single DVD. So even if I could uncompress each file strictly, I
couldn't hold such a big strict bytestring in memory at once.

On 6/25/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

Monday, June 25, 2007, 10:47:11 PM, you wrote:
 bar = fmap decompress $ B.readFile myData.gz
try it with non-lazy bytestrings:
import qualified Data.ByteString as B

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


Re: [Haskell-cafe] Re: Propositional logic question

2007-06-25 Thread Eric

This seems rather complicated! What about this:

A = (B = C)
=  { X = Y   ==  ¬X \/ Y }
   ¬A \/ (¬B \/ C)
=  {associativity}
   (¬A \/ ¬B) \/ C
=  { DeMorgan }
   ¬(A /\ B) \/ C
=  { X = Y   ==  ¬X \/ Y }
   A /\ B   =  C

E.

Dave Tapley wrote:

Whoops, okay after two lines (thanks to oerjan) on #haskell I realise
that yes, it is as easy as it should have been.

For completeness:

[A /\ B]1
 (/\ E1)  [A = (B = C)]2
 A
- (= E)
  B = C
[A /\ B]1
 (/\ E2)
 B  B = C
- (= E)
C
-- (= I)1
(A /\ B) = C

 (= I)2
(A = (B = C)) = ((A /\ 
B) = C)



Learning is fun :)

Dave,
___
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] directory tree?

2007-06-25 Thread Stefan O'Rear
On Mon, Jun 25, 2007 at 12:48:27PM -0700, Chad Scherrer wrote:
 Jedaï,
 
 Are you sure you're not confusing .z with .Z?
 
 http://kb.iu.edu/data/afcc.html
 
 And is it possible that gzip is smarter somehow? Doesn't
 Codec.Compression.GZip call the same C library used by gzip?

gzip: supports gzip, pack, compress

zlib doesn't. http://www.zlib.net/zlib_faq.html#faq12

You ought to just use newpopen or similar
(http://www.cse.unsw.edu.au/~dons/code/newpopen)

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Bryan O'Sullivan

Chad Scherrer wrote:



Now it doesn't complain about too many open files, but instead I get
this runtime error:

LPS *** Exception: user error (Codec.Compression.Zlib: incorrect header 
check)


Are you sure you really have gzip files?  If you're on a Linux or 
similar box, what does file myfile.z report to you?  It should say 
something like gzip compressed data.


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


Re: [Haskell-cafe] Best idiom for avoiding Defaulting warnings with ghc -Wall -Werror ??

2007-06-25 Thread Brandon Michael Moore
On Mon, Jun 25, 2007 at 08:53:18AM -0700, Dave Bayer wrote:
 It continues to appear to me that ghc -Wall -Werror doesn't support  
 small Int constants without a per-use penalty, measured in code length.

Why not use ghc -Wall -Werror -fno-warn-defaulting, maybe with
default(Int)? It removes the potential problems that justified
coding the warning, and turns off the warning.

By the way, using Integer for exponents really shouldn't be less efficient - 
but it seems it is.

The code for (^) should be something like this:

{-# INLINE ^ #-}
n ^ m = case toInteger m of
  S# i - powerInt# n i
  J# a p - powerGmp n a p

(With powerInt# and powerGmp specialized on various types
of n, when there is something to gain).

Then the standard optimizations (inlining, static instance
selection, more inlining, and case of constructor)
should turn n^3 into the same code whether 3 is Int or Integer.

Perhaps GHC.Real needs to be sprinkled with more pragmas.

 Am I the only one blessed/cursed with a vision of how proponents of  
 practical languages would have a field day with this? Perhaps I'm  
 reading too many blogs.

Seeing as it only happens if you specifically ask the compiler
to be as annoying as possible, no reasonable person should take
this much farther than complaining about the GHC warning options.

After all, the type system and purity we claim are generally good
things are still around whatever options you pass, and none of the
justifications for them have much to say one way or the other on
this sort of compiler warning.

I think nobody will argue if you suggest GHC shouldn't complain
about defaulting if only one of the candidate types is actually
usable. It's rather like typeclasses with -fallow-overlapping-instaces.

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Chad Scherrer

On 6/25/07, Bryan O'Sullivan [EMAIL PROTECTED] wrote:

Are you sure you really have gzip files?  If you're on a Linux or
similar box, what does file myfile.z report to you?  It should say
something like gzip compressed data.


Aarrgh, that's the problem - it does use compress. Is the distinction
between .z and .Z not an established standard? I'm guessing there's
not a Haskell interface for compress.

I could just tell the OS to start a gzip process, but I need to be
able to build it here on my Linux box, and run it on various MS
machines. Seems like the best approach at this point might be to
require everyone (only 3 people) to uncompress the data onto the hard
drive first, then go from there.

Thanks for all the help!

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Stefan O'Rear
On Mon, Jun 25, 2007 at 02:13:05PM -0700, Chad Scherrer wrote:
 On 6/25/07, Bryan O'Sullivan [EMAIL PROTECTED] wrote:
 Are you sure you really have gzip files?  If you're on a Linux or
 similar box, what does file myfile.z report to you?  It should say
 something like gzip compressed data.
 
 Aarrgh, that's the problem - it does use compress. Is the distinction
 between .z and .Z not an established standard? I'm guessing there's
 not a Haskell interface for compress.

Very standard.

.z  : always pack
.Z  : always compress
.gz : always gzip

gzip can handle all three, zlib only the last.  (Are you *sure* your
file is compress?)

 I could just tell the OS to start a gzip process, but I need to be
 able to build it here on my Linux box, and run it on various MS
 machines. Seems like the best approach at this point might be to
 require everyone (only 3 people) to uncompress the data onto the hard
 drive first, then go from there.

Or could could reimplement compress in Haskell.  The algorithm is
shockingly simple, and there is a sample implementation (needs
optimization and compress(1) header support, but the LZW engine is
there) is already on the Wiki.  Note that the patent expired in June
'06, so you don't need to worry about that.

http://haskell.org/haskellwiki/Toy_compression_implementations

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Chad Scherrer

On 6/25/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

.z  : always pack
.Z  : always compress
.gz : always gzip

gzip can handle all three, zlib only the last.  (Are you *sure* your
file is compress?)


This means it's compress, doesn't it?

$ file myData.z
myData.z: compress'd data 16 bits


 I could just tell the OS to start a gzip process, but I need to be
 able to build it here on my Linux box, and run it on various MS
 machines. Seems like the best approach at this point might be to
 require everyone (only 3 people) to uncompress the data onto the hard
 drive first, then go from there.

Or could could reimplement compress in Haskell.  The algorithm is
shockingly simple, and there is a sample implementation (needs
optimization and compress(1) header support, but the LZW engine is
there) is already on the Wiki.  Note that the patent expired in June
'06, so you don't need to worry about that.

http://haskell.org/haskellwiki/Toy_compression_implementations


This looks like a lot of fun, but I've got too many other pieces of
code to try to get running efficiently as it is. But I hadn't seen
this link before, and it looks like interesting stuff. Thanks!

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Stefan O'Rear
On Mon, Jun 25, 2007 at 02:42:18PM -0700, Chad Scherrer wrote:
 On 6/25/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 .z  : always pack
 .Z  : always compress
 .gz : always gzip
 
 gzip can handle all three, zlib only the last.  (Are you *sure* your
 file is compress?)
 
 This means it's compress, doesn't it?
 
 $ file myData.z
 myData.z: compress'd data 16 bits

Yep.  (I wonder when the filename got munged?  I suppose it doesn't
matter.)

Recompressing sounds good :)

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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Brandon S. Allbery KF8NH


On Jun 25, 2007, at 14:47 , Chad Scherrer wrote:

LPS *** Exception: user error (Codec.Compression.Zlib: incorrect  
header check)


Keep in mind that GNU gunzip also handles the old compress (.Z) and  
System V pack (.z) formats; I'd expect the Zlib codec to only  
handle gzip format and not the others.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] directory tree?

2007-06-25 Thread Brandon S. Allbery KF8NH


On Jun 25, 2007, at 17:24 , Stefan O'Rear wrote:


.z  : always pack
.Z  : always compress


...unless it's gone through a Windows system or a CD somewhere along  
the way.


Note that gunzip accepts a wide variety of extensions but recognizes  
the files by magic number, *not* by the extension.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Propositional logic question

2007-06-25 Thread Derek Elkins
On Mon, 2007-06-25 at 20:41 +0100, Dave Tapley wrote:
 Hopefully this is just about on topic enough..
 (Oh and it's not home work, I just can't bring myself to let it go!)
 
 Taken from Simon Thompson: Type Theory and Functional Programming
 
 Section 1.1
 Exercise 1.3
 
 Question: Give a proof of (A = (B = C)) = ((A /\ B) = C).

Via the Curry-Howard correspondence, this corresponds to the type of
uncurry ( :: (a - b - c) - (a,b) - c ) and thus uncurry corresponds
to the proof.  The @src lambdabot gives for uncurry is
uncurry f p = f (fst p) (snd p)
which most (careful) Haskell programmers would write as
uncurry f ~(x,y) = f x y

Try to see how the implementation of uncurry matches up to your proof of
the proposition.

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


[Haskell-cafe] Wikipedia archiving bot - code review

2007-06-25 Thread Gwern Branwen
Hey everyone. So I've been learning Haskell for a while now, and I've found the 
best way to move from theory to practice is to just write something useful for 
yourself. Now, I'm keen on editing Wikipedia and I've long wanted some way to 
stop links to external websites from breaking on me. So I wrote this little 
program using the TagSoup library which will download Wikipedia articles, parse 
out external links, and then ask WebCite to archive them.

But there's a problem: no matter how I look at it, it's just way too slow. 
Running on a measly 100 articles at a time, it'll eat up to half my processor 
time and RAM (according to top). I converted it over to ByteStrings since 
that's supposed to be a lot better than regular Strings, but that didn't seem 
to help much.
So I'm curious: in what way could this code be better? How could it be more 
idiomatic or shorter? Particularly, how could it be more efficient either in 
space or time? Any comments are appreciate.

{- Module  :  Main.hs
   License :  public domain
   Maintainer  :  Gwern Branwen [EMAIL PROTECTED]
   Stability   :  unstable
   Portability :  portable
   Functionality: retrieve specified articles from Wikipedia and request 
WebCite to archive all URLs found.
   TODO: send an equivalent request to the Internet Archive.
 Not in any way rate-limited.
   BUGS: Issues redundant archive requests.
 Currently uses Data.ByteString.Lazy.Char8. If I'm understanding the 
documentation right, this barfs
 on the full UTF-8 character set, but Wikipedia definitely exercises 
the full UTF-8 set.
   USE: Print to stdin a succession of Wikipedia article names (whitespace in 
names should be escaped as '_').
A valid invocation might be, say: '$echo Fujiwara_no_Teika 
Fujiwara_no_Shunzei | archive-bot'
All URLs in [[Fujiwara no Teika]] and [[Fujiwara no Shunzei]] would 
then be backed up.
If you wanted to run this on all of Wikipedia, you could take the 
current 'all-titles-in-ns0'
gzipped file from [[WP:DUMP]], gunzip it, and then pipe it into 
archive-bot. -}

module Main where
import Text.HTML.TagSoup (parseTags, Tag(TagOpen))
import Text.HTML.Download (openURL)
import Data.List (isPrefixOf)
import Monad (liftM)
import Data.Set (toList, fromList)
import qualified Data.ByteString.Lazy.Char8 as B (ByteString(), getContents, 
lines, unlines, pack, unpack, words)

main :: IO ()
main = do mapM_ archiveURL = (liftM sortNub $ mapM fetchArticleText = 
(liftM B.words $ B.getContents))
  where sortNub :: [[B.ByteString]] - [B.ByteString]
sortNub = toList . fromList . concat

fetchArticleText :: B.ByteString - IO [B.ByteString]
fetchArticleText article = liftM (B.lines . extractURLs) (openURL(wikipedia ++ 
B.unpack article))
   where wikipedia = http://en.wikipedia.org/wiki/;

extractURLs :: String - B.ByteString
extractURLs arg = B.unlines $ map B.pack ([x | TagOpen a atts - (parseTags 
arg), (_,x) - atts, http://; `isPrefixOf` x])

archiveURL :: B.ByteString - IO String
archiveURL url = openURL(www.webcitation.org/archive?url= ++ (B.unpack url) 
++ emailAddress)
 where emailAddress = [EMAIL PROTECTED]

--
gwern
MAC10 M3 L34A1 Walther MPL AKS-74 HK-GR6 subsonic rounds ballistic media special


pgpPotHursSVu.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia archiving bot - code review

2007-06-25 Thread Neil Mitchell

Hi

You may find that the slow down is coming from your use of the TagSoup
library - I'm currently reworking the parser to make sure its fully
lazy and doesn't space leak. I hope that the version in darcs tomorrow
will have all those issues fixed.

Thanks

Neil


On 6/26/07, Gwern Branwen [EMAIL PROTECTED] wrote:

Hey everyone. So I've been learning Haskell for a while now, and I've found the 
best way to move from theory to practice is to just write something useful for 
yourself. Now, I'm keen on editing Wikipedia and I've long wanted some way to 
stop links to external websites from breaking on me. So I wrote this little 
program using the TagSoup library which will download Wikipedia articles, parse 
out external links, and then ask WebCite to archive them.

But there's a problem: no matter how I look at it, it's just way too slow. 
Running on a measly 100 articles at a time, it'll eat up to half my processor 
time and RAM (according to top). I converted it over to ByteStrings since 
that's supposed to be a lot better than regular Strings, but that didn't seem 
to help much.
So I'm curious: in what way could this code be better? How could it be more 
idiomatic or shorter? Particularly, how could it be more efficient either in 
space or time? Any comments are appreciate.

{- Module  :  Main.hs
   License :  public domain
   Maintainer  :  Gwern Branwen [EMAIL PROTECTED]
   Stability   :  unstable
   Portability :  portable
   Functionality: retrieve specified articles from Wikipedia and request 
WebCite to archive all URLs found.
   TODO: send an equivalent request to the Internet Archive.
 Not in any way rate-limited.
   BUGS: Issues redundant archive requests.
 Currently uses Data.ByteString.Lazy.Char8. If I'm understanding the 
documentation right, this barfs
 on the full UTF-8 character set, but Wikipedia definitely exercises 
the full UTF-8 set.
   USE: Print to stdin a succession of Wikipedia article names (whitespace in 
names should be escaped as '_').
A valid invocation might be, say: '$echo Fujiwara_no_Teika 
Fujiwara_no_Shunzei | archive-bot'
All URLs in [[Fujiwara no Teika]] and [[Fujiwara no Shunzei]] would 
then be backed up.
If you wanted to run this on all of Wikipedia, you could take the 
current 'all-titles-in-ns0'
gzipped file from [[WP:DUMP]], gunzip it, and then pipe it into 
archive-bot. -}

module Main where
import Text.HTML.TagSoup (parseTags, Tag(TagOpen))
import Text.HTML.Download (openURL)
import Data.List (isPrefixOf)
import Monad (liftM)
import Data.Set (toList, fromList)
import qualified Data.ByteString.Lazy.Char8 as B (ByteString(), getContents, 
lines, unlines, pack, unpack, words)

main :: IO ()
main = do mapM_ archiveURL = (liftM sortNub $ mapM fetchArticleText = 
(liftM B.words $ B.getContents))
  where sortNub :: [[B.ByteString]] - [B.ByteString]
sortNub = toList . fromList . concat

fetchArticleText :: B.ByteString - IO [B.ByteString]
fetchArticleText article = liftM (B.lines . extractURLs) (openURL(wikipedia ++ 
B.unpack article))
   where wikipedia = http://en.wikipedia.org/wiki/;

extractURLs :: String - B.ByteString
extractURLs arg = B.unlines $ map B.pack ([x | TagOpen a atts - (parseTags arg), (_,x) 
- atts, http://; `isPrefixOf` x])

archiveURL :: B.ByteString - IO String
archiveURL url = openURL(www.webcitation.org/archive?url= ++ (B.unpack url) 
++ emailAddress)
 where emailAddress = [EMAIL PROTECTED]

--
gwern
MAC10 M3 L34A1 Walther MPL AKS-74 HK-GR6 subsonic rounds ballistic media special

___
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] Tools for Haskell and COM

2007-06-25 Thread shelarcy
Hello Darrell,

On Tue, 26 Jun 2007 03:08:02 +0900, Lewis-Sandy, Darrell [EMAIL PROTECTED] 
wrote:
 Are there any currently maintained tools for interfacing Haskell with COM
 objects?   It appears that both Haskell script and Haskell direct haven't
 been updated since the turn of the century, and have fallen out of step with
 recent library changes.

You can download latest version of H/Direct from CVS,
or hscom that is forked version of H/Direct's comlib from darcs.

http://www.haskell.org/pipermail/libraries/2007-January/006737.html

hscom breaks compatibility from H/Direct. Because developpers edit
hscom by hand instead of to change generating code.

So you must check and choice which is better to use your project.

-- 
shelarcy shelarcyhotmail.co.jp
http://page.freett.com/shelarcy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wikipedia archiving bot - code review

2007-06-25 Thread Donald Bruce Stewart
gwern0:
 Hey everyone. So I've been learning Haskell for a while now, and I've
 found the best way to move from theory to practice is to just write
 something useful for yourself. Now, I'm keen on editing Wikipedia and
 I've long wanted some way to stop links to external websites from
 breaking on me. So I wrote this little program using the TagSoup
 library which will download Wikipedia articles, parse out external
 links, and then ask WebCite to archive them.
 
 But there's a problem: no matter how I look at it, it's just way too
 slow. Running on a measly 100 articles at a time, it'll eat up to half
 my processor time and RAM (according to top). I converted it over to
 ByteStrings since that's supposed to be a lot better than regular
 Strings, but that didn't seem to help much.  So I'm curious: in what
 way could this code be better? How could it be more idiomatic or
 shorter? Particularly, how could it be more efficient either in space
 or time? Any comments are appreciate.
 
 {- Module  :  Main.hs
License :  public domain
Maintainer  :  Gwern Branwen [EMAIL PROTECTED]
Stability   :  unstable
Portability :  portable
Functionality: retrieve specified articles from Wikipedia and request 
 WebCite to archive all URLs found.
TODO: send an equivalent request to the Internet Archive.
  Not in any way rate-limited.
BUGS: Issues redundant archive requests.
  Currently uses Data.ByteString.Lazy.Char8. If I'm understanding the 
 documentation right, this barfs
  on the full UTF-8 character set, but Wikipedia definitely exercises 
 the full UTF-8 set.
USE: Print to stdin a succession of Wikipedia article names (whitespace in 
 names should be escaped as '_').
 A valid invocation might be, say: '$echo Fujiwara_no_Teika 
 Fujiwara_no_Shunzei | archive-bot'
 All URLs in [[Fujiwara no Teika]] and [[Fujiwara no Shunzei]] would 
 then be backed up.
 If you wanted to run this on all of Wikipedia, you could take the 
 current 'all-titles-in-ns0'
 gzipped file from [[WP:DUMP]], gunzip it, and then pipe it into 
 archive-bot. -}
 
 module Main where
 import Text.HTML.TagSoup (parseTags, Tag(TagOpen))
 import Text.HTML.Download (openURL)
 import Data.List (isPrefixOf)
 import Monad (liftM)
 import Data.Set (toList, fromList)
 import qualified Data.ByteString.Lazy.Char8 as B (ByteString(), getContents, 
 lines, unlines, pack, unpack, words)
 
 main :: IO ()
 main = do mapM_ archiveURL = (liftM sortNub $ mapM fetchArticleText = 
 (liftM B.words $ B.getContents))
   where sortNub :: [[B.ByteString]] - [B.ByteString]
 sortNub = toList . fromList . concat
 
 fetchArticleText :: B.ByteString - IO [B.ByteString]
 fetchArticleText article = liftM (B.lines . extractURLs) (openURL(wikipedia 
 ++ B.unpack article))
where wikipedia = http://en.wikipedia.org/wiki/;
 
 extractURLs :: String - B.ByteString
 extractURLs arg = B.unlines $ map B.pack ([x | TagOpen a atts - (parseTags 
 arg), (_,x) - atts, http://; `isPrefixOf` x])
 
 archiveURL :: B.ByteString - IO String
 archiveURL url = openURL(www.webcitation.org/archive?url= ++ (B.unpack url) 
 ++ emailAddress)
  where emailAddress = [EMAIL PROTECTED]
 

you don't seem to be using bytestrings for anything important here --
you just pass them in, and immediately unpack them back to String anyway
-- since tagsoup only downloads String, and parses String. 

Probably, as neil says, TagSoup just isn't optimised much yet. Perhaps
try the bytestring-based urlcheck?

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/urlcheck-0.1

Neil, perhaps tagsoup should provide at the bottom a bytestring layer --
so there's some hope of efficient downloading, with a String layer on
top -- not the other way around?

-- Don

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