[Haskell-cafe] Is id strict?

2006-07-30 Thread David House

Hi all.

I've seen two definitions of a 'strict function', which I'm trying to
unite in my mind:

1) f is strict iff f _|_ = _|_.
2) f is strict iff it forces evaluation of its arguments.

There is a large sticking point that in my minds seems to fit (1) but
not (2): id. Clearly,  id undefined is undefined, but I also don't
think id forces evaluation of its argument. There was a
mini-discussion concerning this topic last night on #haskell, but if
there was a consensus conclusion, it passed me by.

Thanks in advance.

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


Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
On 29.07 14:07, Brian Sniffen wrote:
 I'm very excited by the ability to pass functions or IO actions
 between threads of the same program.  But I don't see any language or
 library support for doing so between programs, or between sessions
 with the same program.  OCaml provides a partial solution:
 
 http://caml.inria.fr/pub/docs/manual-ocaml/libref/Marshal.html
 
 Though all it's really sending is an address and a hash of the binary
 program.  Even SerTH doesn't help with functional types.  I seek the
 knowledge of the Haskell Cafe: is there a reasonable way of addressing
 this problem?

There is sadly no real good way of doing it on top of GHC. If both
sides are running an identical executable image one can hack it to
work (see parallel Haskell for the code to do it). But in general
I don't think it is worth the trouble. The problem is:

1) versioning (I like being able to upgrade applications while keeping 
serialized state)
2) trust (GHC does not have sandboxing)

YHC may have an answer for YHC users.

I have some code which allows one to register functions and call them
transparently over a network - even supporting callbacks. Thus code
does not move, but code location is quite transparent.

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


[Haskell-cafe] Re: Is id strict?

2006-07-30 Thread Jón Fairbairn
David House [EMAIL PROTECTED] writes:

 Hi all.
 
 I've seen two definitions of a 'strict function', which I'm trying to
 unite in my mind:
 
 1) f is strict iff f _|_ = _|_.
 2) f is strict iff it forces evaluation of its arguments.
 
 There is a large sticking point that in my minds seems to fit (1) but
 not (2): id. Clearly,  id undefined is undefined, but I also don't
 think id forces evaluation of its argument. There was a
 mini-discussion concerning this topic last night on #haskell, but if
 there was a consensus conclusion, it passed me by.
 
 Thanks in advance.

In (2), you have to be evaluating f on an argument before f
can force the argument.  If you evaluate id x, you
necessarily evaluate x.  I don't think (2) is a very good
definition, since I don't know what forces means here.

-- 
Jón Fairbairn [EMAIL PROTECTED]


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


Re: [Haskell-cafe] Is id strict?

2006-07-30 Thread Ian Lynagh
On Sun, Jul 30, 2006 at 09:44:25AM +0100, David House wrote:
 
 I've seen two definitions of a 'strict function', which I'm trying to
 unite in my mind:
 
 1) f is strict iff f _|_ = _|_.
 2) f is strict iff it forces evaluation of its arguments.
 
 There is a large sticking point that in my minds seems to fit (1) but
 not (2): id.

If the value of (id x) is demanded then the value of x will always be
demanded. Therefore id is strict in its first argument.

If x is _|_ then this implies the result of f x will also be _|_, as per
the f is strict = f _|_ = _|_ half of your 1).
f _|_ = _|_ = f is strict is not true, e.g. for f _ = f 'a'.

In place of your 2), I would say
(f x0 .. xn) is strict in xi if demanding the value of (f x0 .. xn)
requires demanding the value of xi.

(demanding the value in the above means evaluating to weak head normal
form).

Hope that helps.


Thanks
Ian

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


[Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley

Hi -

Part 1 of 2 - Monoid versus MonadPlus
===

I've just run into a troublesome question when trying to design a sequence 
class:


   class ISeq c a | c - a where
empty :: c
single :: a - c
append :: c - c - c

However I've noticed that people sometimes separate the empty and append 
operations out as sequences with these ops form a Monoid therefore:


class Monoid c = ISeq c a | c - a where
single :: a - c

-- now outside the class
append :: ISeq c a = c - c - c
append = mappend

empty :: ISeq c a = c
empty = mempty

Another option, is the Edison library which uses:

class (Functor s, MonadPlus s) = Sequence s where

so here MonadPlus is used instead of Monoid to provide empty and append.
So I've got three main questions:

1) Did Edison choose MonadPlus just because this fitted in with the lack of 
multi-parameter typeclasses in H98?


2) Are there any reasons to prefer the Edison design over the MPTC design 
(apart from H98 compatibility) or vice versa?


3) Is it worth bothering to derive ISeq from Monoid (with the possible extra 
inefficiency of the indirection through the definitions for append = mappend 
etc or does the compiler completely optimize this out)?


and a fourth more long term question:

4) Would it be worth reconsidering the rules for top level names so that 
class methods could always be local to their class (ditto for value 
constructors and field names being local to their type constructor). For 
example it would be nice imho to be able to write:


 class Monoid c = ISeq c a | c - a where
 length :: c - Int


 f x y = Monoid/append x y -- or ISeq/append x y
 g x  = ISeq/length x

instead of having all names collide in the top level of a module, since at 
the moment it is difficult to think of method names that don't collide with 
the Prelude, and it's not nice to have to write mempty in place of 
empty.


Part 2 of 2 - Monad versus Ancillary result type


Another issue relates to left and right views of a sequence. If a sequence 
is non-empty, the left view is just the leftmost element and the rest of the 
sequence. The problem arises when the sequence is empty. In the Edison 
library, this is solved by returning a monadic value ie:


lview :: Monad m = s a - m (a, s a)

whereas from the paper Finger trees: a simple general purpose data 
structure by Ralf Hinze and Ross Paterson they use an ancillary data type 
to store the result of a view:


   data ViewL s a = NilL | ConsL a (s a)

   viewL :: FingerTree a - ViewL FingerTree a

So my question here is: what's the best choice? I can see that the monadic 
version has the advantage that it could be used in do notation in cases 
where you expect the sequence to be non-empty, but has the disadvantage that 
it treats the empty sequence as something special (resulting in Monad/fail) 
and an extra indirection to find the components when the sequence is 
non-empty.


Anyway these are my main questions for now - any feedback appreciated ;-)

Thanks, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Is id strict?

2006-07-30 Thread David House

On 30/07/06, Ian Lynagh [EMAIL PROTECTED] wrote:

If the value of (id x) is demanded then the value of x will always be
demanded. Therefore id is strict in its first argument.

...

In place of your 2), I would say
(f x0 .. xn) is strict in xi if demanding the value of (f x0 .. xn)
requires demanding the value of xi.


Ah. Very helpful. Thanks.

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


Re: [Haskell-cafe] Baffled by Disk IO

2006-07-30 Thread Florian Weimer
* SevenThunders:

 OK it was stupid.  Apparently GHC behaves differently according to what the
 name of the high level source file is.  If I renamed test.hc to main.hc
 everything works the same as GHCi.  I probably should actually read the
 manual some day.

Some operating systems have a test program, which gets called if you
just enter test.  Try using ./test and see if it makes a
difference.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Is id strict?

2006-07-30 Thread Duncan Coutts
On Sun, 2006-07-30 at 10:56 +0100, Jón Fairbairn wrote:
 David House [EMAIL PROTECTED] writes:
 
  Hi all.
  
  I've seen two definitions of a 'strict function', which I'm trying to
  unite in my mind:
  
  1) f is strict iff f _|_ = _|_.
  2) f is strict iff it forces evaluation of its arguments.
  
  There is a large sticking point that in my minds seems to fit (1) but
  not (2): id. Clearly,  id undefined is undefined, but I also don't
  think id forces evaluation of its argument. There was a
  mini-discussion concerning this topic last night on #haskell, but if
  there was a consensus conclusion, it passed me by.
  
  Thanks in advance.
 
 In (2), you have to be evaluating f on an argument before f
 can force the argument.  If you evaluate id x, you
 necessarily evaluate x.  I don't think (2) is a very good
 definition, since I don't know what forces means here.

Surely it just means evaluate to weak head normal form?

Definition 2) relies on following a certain evaluation strategy: that
operationally, functions always return results in weak head normal form.
GHC follows this strategy. It's possibly to imagine returning thunks and
then getting the caller to force the evaluation to WHNF.

So under the latter model, 'id' would operationally do nothing. It would
not force its argument. Under the more sensible model 'id' does force
its argument to WHNF before returning.

Duncan

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


[Haskell-cafe] Re: Is id strict?

2006-07-30 Thread Jón Fairbairn
Duncan Coutts [EMAIL PROTECTED] writes:

 On Sun, 2006-07-30 at 10:56 +0100, Jón Fairbairn wrote:
  David House [EMAIL PROTECTED] writes:
   1) f is strict iff f _|_ = _|_.
   2) f is strict iff it forces evaluation of its arguments.
  
  In (2), you have to be evaluating f on an argument before f
  can force the argument.  If you evaluate id x, you
  necessarily evaluate x.  I don't think (2) is a very good
  definition, since I don't know what forces means here.
 
 Surely it just means evaluate to weak head normal form?

Means [what] evaluate[s] to whnf? id doesn't do any
evaluating, in fact functions in general don't do any
evaluating.

 Definition 2) relies on following a certain evaluation strategy: that
 operationally, functions always return results in weak head normal form.
 GHC follows this strategy. It's possibly to imagine returning thunks and
 then getting the caller to force the evaluation to WHNF.

Which is pretty much my point. Use a definition of strict
that doesn't depend on anything but denotations (or Böhm
trees).

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Cabal in ghc 6.4.2

2006-07-30 Thread Duncan Coutts
On Sun, 2006-07-30 at 15:01 +0100, allan wrote:

 however with version 6.4.2 I get the following error:
 
 haskellprint$ ./Setup.hs  build
 Preprocessing executables for haskellprint-0.1...
 Building haskellprint-0.1...
 Chasing modules from: Main.hs
 Could not find module `Text.ParserCombinators.Parsec':
   use -v to see a list of the files searched for
   (imported from ./Parser.hs)

The Text.ParserCombinators.Parsec modules are in the parsec module.

 build-depends:  base

Add parsec here:

build-depends:  base, parsec


The reason it works when you run it without -hide-all-packages is that
by default for convenience all packages are 'exposed'. That is they can
be used without explicitly having to specify them. However it was felt
that for distributing software, which is one of the main purposes of
Cabal, one should be fully explicit about the dependencies so that users
compiling on other machines know exactly what packages needed and don't
end up with mysterious import errors.

Now it's true that Cabal could be a bit cleverer here and warn you
before it even starts compiling that you have not specified all the
right packages in the build-depends. At the moment however Cabal doesn't
have a proper imports chaser so it can't do this.

Duncan

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


Re: [Haskell-cafe] Re: Is id strict?

2006-07-30 Thread Duncan Coutts
On Sun, 2006-07-30 at 13:22 +0100, Jón Fairbairn wrote:
 Duncan Coutts [EMAIL PROTECTED] writes:
 
  On Sun, 2006-07-30 at 10:56 +0100, Jón Fairbairn wrote:
   David House [EMAIL PROTECTED] writes:
1) f is strict iff f _|_ = _|_.
2) f is strict iff it forces evaluation of its arguments.

  Definition 2) relies on following a certain evaluation strategy: that
  operationally, functions always return results in weak head normal form.
  GHC follows this strategy. It's possibly to imagine returning thunks and
  then getting the caller to force the evaluation to WHNF.
 
 Which is pretty much my point. Use a definition of strict
 that doesn't depend on anything but denotations (or Böhm
 trees).

Yes, for being precise a denotational approach is simpler.

However for an intuition about how strictness affects evaluation order
and space and performance behaviour I find that 2) is quite a helpful
way to look at things. It allows you to look at a function and ask: if I
demand the result in WHNF (which I know will happen if the function is
called at runtime) what demand will that place on other expressions,
variables and arguments.

The discussion on #haskell went on to conclude that we need better tools
for showing us the inferred strictness of functions we write (eg by
getting the compiler to tell us). It was also noted that many Haskell
programmers, especially beginners have very little intuition about
strictness and so can't get themselves out of troubles caused by too
much or to little strictness, like performance problems, memory leaks
and exceptions slipping past exception handlers.

Duncan

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


Re: [Haskell-cafe] Cabal in ghc 6.4.2

2006-07-30 Thread allan



The Text.ParserCombinators.Parsec modules are in the parsec module.

  

build-depends:  base



Add parsec here:

build-depends:  base, parsec


The reason it works when you run it without -hide-all-packages is that
by default for convenience all packages are 'exposed'. That is they can
be used without explicitly having to specify them. However it was felt
that for distributing software, which is one of the main purposes of
Cabal, one should be fully explicit about the dependencies so that users
compiling on other machines know exactly what packages needed and don't
end up with mysterious import errors.

  

Yip this sounds like a good policy to me too.


Now it's true that Cabal could be a bit cleverer here and warn you
before it even starts compiling that you have not specified all the
right packages in the build-depends. At the moment however Cabal doesn't
have a proper imports chaser so it can't do this.

Duncan
  


Thanks very much for the response, however, adding parsec to the 
build-depends of the .cabal file now causes a slightly different error, 
and in fact this is the same error I get with my other project:

haskellprint$ ./Setup.hs  build
Preprocessing executables for haskellprint-0.1...
Building haskellprint-0.1...
Chasing modules from: Main.hs
Could not find module `Char':
 use -v to see a list of the files searched for
 (imported from ./Parser.hs)
haskellprint$


so basically I was expecting 'Char' to be in the 'base' package, I guess 
this is wrong?


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


Re: [Haskell-cafe] Cabal in ghc 6.4.2

2006-07-30 Thread Neil Mitchell

Hi


so basically I was expecting 'Char' to be in the 'base' package, I guess
this is wrong?


Yes, Char is in the haskell98 package, the new name for Char is
Data.Char which exports a bit more. Either add haskell98 as a package,
or replace Char with Data.Char (which is in base), I'd recommend the
latter, but either should work.

Thanks

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


Re: [Haskell-cafe] Cabal in ghc 6.4.2

2006-07-30 Thread allan




Yes, Char is in the haskell98 package, the new name for Char is
Data.Char which exports a bit more. Either add haskell98 as a package,
or replace Char with Data.Char (which is in base), I'd recommend the
latter, but either should work.

Thanks

Neil

a ha, that works, thank you both very much, I can sleep easy now.

allan

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Robert Dockins
On Sunday 30 July 2006 07:47, Brian Hulley wrote:
 Hi -

 Part 1 of 2 - Monoid versus MonadPlus
 ===

 I've just run into a troublesome question when trying to design a sequence
 class:

 class ISeq c a | c - a where
  empty :: c
  single :: a - c
  append :: c - c - c

 However I've noticed that people sometimes separate the empty and append
 operations out as sequences with these ops form a Monoid therefore:

  class Monoid c = ISeq c a | c - a where
  single :: a - c

  -- now outside the class
  append :: ISeq c a = c - c - c
  append = mappend

  empty :: ISeq c a = c
  empty = mempty

 Another option, is the Edison library which uses:

  class (Functor s, MonadPlus s) = Sequence s where

 so here MonadPlus is used instead of Monoid to provide empty and append.
 So I've got three main questions:

 1) Did Edison choose MonadPlus just because this fitted in with the lack of
 multi-parameter typeclasses in H98?

Edison's design hails from a time when MPTCs were not only non-standard (as  
they still are), but also not widely used, and before fundeps were avaliable 
(I think).  So the answer to this one is pretty much yes.  I've considered 
reformulating the Sequence class to be more similar to the Collection classes 
(which use MPTCs, fundeps and mention the element type), but for the 1.2 
version I wanted to make as few changes as I thought I could to the overall 
design decisions.

In fact, I will likely make this change at some point.  It would allow, eg, 
making Don's ByteString (or whatever it's called now, I forget) an instance 
of Sequence, which is currently impossible.  OTOH, it would require 
sacrificing the Functor, Monad and MonadPlus instances...

 2) Are there any reasons to prefer the Edison design over the MPTC design
 (apart from H98 compatibility) or vice versa?

H98 is probably the big one.  I'm currently in wait-and-see mode concerning 
MPTCs and especially fundeps.  As Edison maintainer, I've tried to use them 
sparingly in the hope that Edison can be made Haskell' compliant (crosses 
fingers).  Aside: I hope the Haskell' committee makes some sort of decision 
here soonish.

 3) Is it worth bothering to derive ISeq from Monoid (with the possible
 extra inefficiency of the indirection through the definitions for append =
 mappend etc or does the compiler completely optimize this out)?

Not sure about this one.  I suspect, however, that the appropriate SPECIALIZE 
pragmas could cover any cases that you really care about.

 and a fourth more long term question:

 4) Would it be worth reconsidering the rules for top level names so that
 class methods could always be local to their class (ditto for value
 constructors and field names being local to their type constructor).

[snip more question]

No comment.

 Part 2 of 2 - Monad versus Ancillary result type
 

 Another issue relates to left and right views of a sequence. If a sequence
 is non-empty, the left view is just the leftmost element and the rest of
 the sequence. The problem arises when the sequence is empty. In the Edison
 library, this is solved by returning a monadic value ie:

  lview :: Monad m = s a - m (a, s a)

 whereas from the paper Finger trees: a simple general purpose data
 structure by Ralf Hinze and Ross Paterson they use an ancillary data type
 to store the result of a view:

 data ViewL s a = NilL | ConsL a (s a)

 viewL :: FingerTree a - ViewL FingerTree a

 So my question here is: what's the best choice? I can see that the monadic
 version has the advantage that it could be used in do notation in cases
 where you expect the sequence to be non-empty, but has the disadvantage
 that it treats the empty sequence as something special (resulting in
 Monad/fail) and an extra indirection to find the components when the
 sequence is non-empty.

Well, the empty sequence IS special, when it comes to looking the leftmost 
(resp. righmost) element.  You have to deal somehow with the fact that the 
operation is a partial function.

I think the arbitrary monad option is better.  It gives the user more 
flexibility about how to use the operation.  Really the only way to use ViewL 
is to put it inside a case of.  With a monad you can use any of the 
plethora of monadic operations and, as you mentioned, the do notation.  In 
addition, if you want the use case of ViewL, you can always use the Maybe 
monad.

I'm not inclined to worry too much about the extra indirection, which seems 
like a viable target for being erased by the compiler (I've not tested if 
this happens, however).


 Anyway these are my main questions for now - any feedback appreciated ;-)


BTW, for what purpose are you desiging a new sequence class?  You are clearly 
aware of other efforts in this area; in what ways to they not meet your 
needs?


 Thanks, Brian.


-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, 

Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Jason Dagit

On 7/30/06, Einar Karttunen ekarttun@cs.helsinki.fi wrote:

On 29.07 14:07, Brian Sniffen wrote:
 I'm very excited by the ability to pass functions or IO actions
 between threads of the same program.  But I don't see any language or
 library support for doing so between programs, or between sessions
 with the same program.  OCaml provides a partial solution:

 http://caml.inria.fr/pub/docs/manual-ocaml/libref/Marshal.html

 Though all it's really sending is an address and a hash of the binary
 program.  Even SerTH doesn't help with functional types.  I seek the
 knowledge of the Haskell Cafe: is there a reasonable way of addressing
 this problem?

There is sadly no real good way of doing it on top of GHC. If both
sides are running an identical executable image one can hack it to
work (see parallel Haskell for the code to do it). But in general
I don't think it is worth the trouble. The problem is:

1) versioning (I like being able to upgrade applications while keeping 
serialized state)
2) trust (GHC does not have sandboxing)


Depending on the type of sandboxing that you need/want #2 might be
possible with GHC.  Take lambdabot for example.  lambdabot has made it
safe to allow arbitrary expression evaluation by disallowing IO and
not importing unsafePerformIO and similar unsafe functions.

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


Re: [Haskell-cafe] Baffled by Disk IO

2006-07-30 Thread SevenThunders

Yes I do have another test on my path.  It is in a utilities directory of
unix like commands that have been ported to windows.  However I also have a
test.exe that was created by ghc that seems to do nothing, even if I type
./test.exe.  Thanks for the hint though.
-- 
View this message in context: 
http://www.nabble.com/Baffled-by-Disk-IO-tf2021760.html#a5566155
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Baffled by Disk IO

2006-07-30 Thread SevenThunders


Florian Weimer wrote:
 
 * SevenThunders:
 
 OK it was stupid.  Apparently GHC behaves differently according to what
 the
 name of the high level source file is.  If I renamed test.hc to main.hc
 everything works the same as GHCi.  I probably should actually read the
 manual some day.
 
 Some operating systems have a test program, which gets called if you
 just enter test.  Try using ./test and see if it makes a
 difference.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

Sorry forgot to quote the original message.
and my reply:

Yes I do have another test on my path.  It is in a utilities directory of
unix like commands that have been ported to windows.  However I also have a
test.exe that was created by ghc that seems to do nothing, even if I type
./test.exe.  Thanks for the hint though.
-- 
View this message in context: 
http://www.nabble.com/Baffled-by-Disk-IO-tf2021760.html#a5566174
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Serializing Functions and Actions for Distributed Programming

2006-07-30 Thread Einar Karttunen
On 30.07 12:12, Jason Dagit wrote:
 Depending on the type of sandboxing that you need/want #2 might be
 possible with GHC.  Take lambdabot for example.  lambdabot has made it
 safe to allow arbitrary expression evaluation by disallowing IO and
 not importing unsafePerformIO and similar unsafe functions.


This is possible as lambdabot has the source code rather than
an arbitrary Haskell expression at runtime.

Basically how does one differentiate between:

(\x - unsafePerformIO somethingNasty `seq` (x+1))
and
(\x - x + 1)

at runtime.

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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley

Robert Dockins wrote:

On Sunday 30 July 2006 07:47, Brian Hulley wrote:

Another option, is the Edison library which uses:

 class (Functor s, MonadPlus s) = Sequence s where

so here MonadPlus is used instead of Monoid to provide empty and
append. So I've got three main questions:



1) Did Edison choose MonadPlus just because this fitted in with the
lack of multi-parameter typeclasses in H98?

Edison's design hails from a time when MPTCs were not only
non-standard (as they still are), but also not widely used, and
before fundeps were avaliable (I think).  So the answer to this one
is pretty much yes.

[snip]

Hi - Thanks for the answers to this and my other questions. One thing I just 
realised is that there doesn't seem to be any instance declarations anywhere 
in the standard libs relating Monoid to MonadPlus so it's a bit unsettling 
to have to make a random choice on the question of what kind of object a 
Sequence is...


I tried:

   class (forall a. Monoid s a) = Sequence s where ...

but of course that doesn't work, so I suppose MonadPlus is the only option 
when 'a' doesn't appear as a type variable arg of the class being defined.



BTW, for what purpose are you desiging a new sequence class?  You are
clearly aware of other efforts in this area; in what ways to they not
meet your needs?


The existing sequence and collection classes I've looked at don't do enough.

For example, when I tried to represent the text in an edit widget, I 
realised I needed a sequence of characters that could also be considered to 
be a sequence of lines, and it is necessary to be able to index the sequence 
by character position as well as by line position, as well as keeping track 
of the total number of characters, the total number of lines, and the 
maximum number of characters on any one line (so as to be able to calculate 
the x,y extents when laying out the widget, assuming a fixed width font 
(tabs ignored!)), with very efficient split and append operations.


I managed to get a good representation by using a FingerTree of lines where 
each line uses a ByteString.
I made my own FingerTree class based on the one referenced in the paper at 
http://www.soi.city.ac.uk/~ross/papers/FingerTree.html but without the 
symbolic names which I find totally unreadable and confusing, and also so I 
could get full control of the strictness of the implementation, and also as 
a way of understanding them since I'd never come across such a complicated 
data structure before. (I highly recommend this paper to anyone who wants to 
learn about FingerTrees, Monoids and other very useful concepts.)


So one thing existing sequence classes don't have (apart from FingerTree) is 
the concept of measurement which is essential when you want efficient 
updates. Eg in my text buffer, the measurement maintained for a sequence is 
the number of chars and number of lines and maximum line length.


Then I needed a structure for a Trie widget a bit like (details omitted):

 data Node = Expanded Value T | Collapsed Value T | Leaf Value
 newtype T = T (FingerTree (Key, Node))

where objects of type T could be regarded as a finite map (eg from 
hierarchical module names to modules) as well as a flattened linear sequence 
indexed by line number (for display on the screen in a widget given the 
current scroll bar position), and which also needed to keep track of the 
total horizontal and vertical extent of the Trie as it would appear in the 
widget's font.


There are several different kinds of measurement going on in this data 
structure, as well as the complexity of the extra recursion through the leaf 
to a new level. Existing sequence abstractions don't seem to provide the 
operations needed to treat a nested data structure as a single sequence.


In summary:

1) Often a complex data structure must be able to be simultaneously regarded 
as a single flattened sequence
2) Measurements are needed for efficient updates (may need to keep track of 
several at once)
3) Indexing and size are sometimes needed relative to the flattened sequence 
not just the top level
4) It is useful to have a finite map that can also be regarded as a linear 
sequence
5) Such finite maps may also be nested (when the keys are hierarchical) but 
this nesting should be hidden from the user...
6) I want a design that can allow complex data structures to be built up 
easily and instanced to the appropriate interfaces
7) Also naming conventions in the existing libs are a bit irregular and 
burdened with old fashioned lisp-isms eg in Data.Edison.Seq there are 
functions lview and reducel but I'd argue that there must be one and 
only one way of forming any identifier in any program namely that the 
function should appear first followed by qualifiers (so that related 
functionality always appears together in a lexicographical listing of 
functions) and it must use camel case with no exceptions at all, thus 
viewL and reduceL (and foldL).
8) More factoring needs to 

[Haskell-cafe] The possibility of a real OS based on Haskell zippers

2006-07-30 Thread Andy Elvey
Hi everyone - 

 I'm very much a Haskell newbie, but have followed Haskell (and the
various Haskell sites) for quite a few months now, and I absolutely
*love* the language. 

 One thing that **fascinated** me a while ago was the site which gave
Haskell code for a Haskell-based fileserver/OS using zippers (the URI
follows) - 
 
 http://okmij.org/ftp/Computation/Continuations.html#zipper 

 That code looks amazing! 

 So, I was thinking - would it *actually be (theoretically) possible* to
create a real booting OS (a bit like House) from the above code? 
By a real OS, I mean something that uses (say) GRUB, and at least has
a command-line of some kind. ( A GUI could come later ... ).

I think that a Plan 9-ish OS (with all its namespace/URL stuff, and
its network-centric approach) would seem to be *particularly well
suited* to being done using Haskell. 

( I have to say that I love Plan 9's elegance, but I just *can't* manage
its controls/GUI, they have me flummoxed ... )
  
If it were possible, I would *love* to see it - I've actually seriously
considered even coughing up say $100 to $200 or so for a contest to
create such a thing

Anyway, first things first :-) - is such an OS possible?  

Many thanks for your time - bye for now - 
 - Andy 

 

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