Re: [Haskell-cafe] (weird stuff) Kernel Modules in Haskell ;-)

2009-09-15 Thread minh thu
2009/9/15 Matthias Kilian :
> A fellow openbsd developer told me the URL below...
>
> I hope this hasn't been posted on this list already (at least I
> didn't find it in my local archives):
>
> http://tommd.wordpress.com/2009/09/13/kernel-modules-in-haskell/

I don't think it was posted here, but it was on reddit. You might want
to follow it.

http://www.reddit.com/r/haskell

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


[Haskell-cafe] A thought about liberating Haskell's syntax

2009-09-15 Thread George Pollard
Dear all,

Here is a note concerning a thought I just had. I have written a rough
sketch/outline and
would like feedback upon this.

The beginning thought: I would like to be able to write new
bracket-like operators
without having to rewrite GHC. (Case in point: applicative brackets.)

First idea is to make them Template Haskell so we can mess with the
internals (write custom list/set comprehension implementations).
However a type (String → Exp) is not good enough; parsing the
String is too much work! (Think precedence, etc.)
We want to be able to have something (Exp → Exp).

For this, we probably also need Template Haskell versions of
normal (infix) operators, so that we can have something like:

 template infixr , (-1) -- lower precedence than $
 a, b = if isList b
then a : b
else a : [b]

Problem with this;

 [x, [y,z]] would have type :: [α]

Lists constructed with ',' should have a different type from normal
lists; call it QList.

 , :: Exp → Exp → Exp
 a, b@(AppE (ConE 'QCons) _) = a `qcons` b
 a, b = a `qcons` (b `qcons` QNil)
 where
qcons a b = (ConE 'QCons) `AppE` a `AppE` b

 {- NB: we also need to provide implementations for type and pattern
contexts, see next section. -}

I believe that with this we can have the tuple and list syntax not
hard-coded in.
An example:

 -- note we need to provide the context for TH: Pattern, Expression, or Type
 -- no thought to sections here
 -- how to add tuple sections?
-- perhaps relax operator rules for templates so that a, , , b is legitimate

 template outfix ( ) expression = (\x → case x of
(QCons _ _) → TupE $ fromQList x
_   → x

 template outfix ( ) pattern = (\x → case x of
(QCons _ _) → TupP $ fromQList x
_   → x

 template outfix ( ) type = (\x → case x of
(QCons _ _) → foldl (\z x → z `AppT` x) (TupleT (length x)) x
_   → x

Anyway, we could then have easily-written syntax for;
 - sets
 - applicative brackets
 - parallel list comprehensions wouldn't have to be hardcoded
(provide something like the above ',' but '|' returning something
else. Perhaps QList should be tagged by a phantom type.)
 - statically-lengthed vectors

Problems I can see:
- QList (or other use-only-for-x types) could turn up in an actual program;
  l = a, b :: QList α
 -- is this actually a problem?
- "Hidden" rewriting/macros not really the Template Haskell way, this
is more scheme-like.

A further (possibly evil) extension:

  template outfix do {-outdent-} expression = ... >:)
  -- would require thinking about EOL handling/semi-colon insertion
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] adding state in GUIs (qtHaskell)

2009-09-15 Thread Alp Mestan
On Fri, Sep 11, 2009 at 5:55 PM, Jeremy O'Donoghue <
jeremy.odonog...@gmail.com> wrote:

> 
>
> I don't have anything as neat to show you as Duncan's suggetion (I'd also
> be interested to see a cleaner way to do it - this sort of code always
> grates a little with me, although all of the major Haskell GUI bindings seem
> to need a similar programming style.
>
> However, at the most basic 'trying it out' level, I suspect that something
> very like this will work just as well for qtHaskell as it does for
> wxHaskell.
> Regards
> Jeremy
>

Very interesting code. However, I'd be very curious to see if qthaskell
handles .ui files. And how it does. With C++, thanks to the 'uic' command
line tool, we generate a class from the .ui file, and then just have to
store an instance of it in our window/dialog/widget/whatever. This class has
a setupUI member function, taking a QWidget*/QDialog*/QMainWindow*/whatever,
which initializes all the ui components and put them on our widget just like
we asked it to do in the designer.

Actually, I'm wondering how the trick could be done (and if it is already
done ?) in Haskell without letting too much things generated and compiled at
the C++ level with some FFI magic.


-- 
Alp Mestan
http://blog.mestan.fr/
http://alp.developpez.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Building a monoid, continuation-passing style

2009-09-15 Thread Derek Elkins
On Mon, Sep 14, 2009 at 10:25 AM, Martijn van Steenbergen
 wrote:
> Hello cafe,
>
> Inspired by Sean Leather's xformat package [1] I built a datatype with which
> you can build a monoid with holes, yielding a function type to fill in these
> holes, continuation-passing style. Here are some primitives and their types:
>
>> now   :: m -> ContSt m r r
>> later :: (a -> m) -> ContSt m r (a -> r)
>> run   :: ContSt m m r -> r
>> instance Monoid m => Category (ContSt m)
>
> Here's an example of how to use it:
>
>> run (now "hello" . now "world")
>
> "helloworld"
>
>> run (later id . now "world") "hello"
>
> "helloworld"
>
>> run (later id . later show) "hello" 567
>
> "hello567"
>
> The source code is available at [2].
>
> I have a couple of questions:
> * ContSt is a Category. Is it also an Arrow? Why (not)?
> * Did I miss any other obvious classes this type is an instance of?
> * What is its relation with the Cont and Reader monads?
> * Are there any other useful applications other than printf-like
> functionality?
> * ContSt is a horrible name. What is a better one?
>
> For those who have a bit more time: I appreciate any comments and
> suggestions on the code. :-)

I believe this technique is based on a technique introduced in Olivier
Danvy's "Functional Unparsing".  While not immediately applicable to
Haskell unless you want to make/use a delimited continuation monad,
you may find the paper "On Typing Delimited Continuations: Three New
Solutions to the Printf Problem" by Kenichi Asai interesting.  It is
available at the following url:
http://pllab.is.ocha.ac.jp/~asai/papers/papers.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Building a monoid, continuation-passing style

2009-09-15 Thread David Menendez
On Mon, Sep 14, 2009 at 11:25 AM, Martijn van Steenbergen
 wrote:
> Inspired by Sean Leather's xformat package [1] I built a datatype with which
> you can build a monoid with holes, yielding a function type to fill in these
> holes, continuation-passing style.

Neat!

> I have a couple of questions:
> * ContSt is a Category. Is it also an Arrow? Why (not)?

I think it isn't. To be an Arrow, you need a definition for first, and
to write first you need to be able to transform a function of type f r
-> a into a function of type f (r,b) -> (a,b), which I'm pretty sure
is impossible.

> * What is its relation with the Cont and Reader monads?

I'm reminded of the parameterized monad of continuations that Oleg
mentioned a few years back.



Here's one way of expressing it:

class Paramonad m where
ret :: a -> m x x a
bind :: m x y a -> (a -> m y z b) -> m x z b

liftP2 :: (Paramonad m) => (a -> b -> c) -> m x y a -> m y z b -> m x z c
liftP2 (*) m1 m2 = m1 `bind` \a -> m2 `bind` \b -> ret (a * b)

newtype Cont x y a = Cont { runCont :: (a -> y) -> x }

run :: Cont x a a -> x
run m = runCont m id

instance Paramonad Cont where
ret a = Cont $ \k -> k a
m `bind` f = Cont $ \k -> runCont m (\a -> runCont (f a) k)

shift :: ((a -> Cont z z y) -> Cont x b b) -> Cont x y a
shift f = Cont $ \k -> run $ f (ret . k)


(<>) :: Monoid m => Cont x y m -> Cont y z m -> Cont x z m
(<>) = liftP2 mappend

later :: (a -> m) -> Cont (a -> r) r m
later f = shift $ \k -> ret (run . k . f)

-- equivalently,
-- later f = Cont $ \k -> k . f


> run (ret "x" <> ret "y")
"xy"

> run (ret "x" <> later id) "y"
"xy"

and so forth.


In fact, this is a good candidate for an alternative implementation.

newtype ContSt m r a = ContSt (Cont a r m)

It would be interesting to compare their relative efficiency.

> * ContSt is a horrible name. What is a better one?

HoleyMonoid?

-- 
Dave Menendez 

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


Re: [Haskell-cafe] algebra/grammar/language for expressing time intervals

2009-09-15 Thread Iain Alexander
You might want to take a look at
RFC 2445
Internet Calendaring and Scheduling Core Object Specification
Section 4.8.5.4 Recurrence Rule
-- 
Iain Alexander  i...@stryx.demon.co.uk

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


[Haskell-cafe] loading object code with ghci

2009-09-15 Thread Ryan Wisnesky

Hello,

I'm having some trouble correctly linking to externally generated  
object code when using ghci.  I'm loading a Cabal package Foo, that  
has already been successfully installed:


>ghci -package Foo
ghc-6.8.3:
unknown symbol `_iceExePath'
Loading package Foo-0.1 ... linking ... ghc-6.8.3: unable to load  
package `Foo-0.1'


I have a file Bar.o which contains the definition of _iceExePath:

>nm ./Bar.o
 ...
U _ProcessInformationCopyDictionary
00a0 b _exepath
 T _iceExePath
U _kCFBundleExecutableKey
...

The documentation at http://www.haskell.org/ghc/docs/6.8.3/html/users_guide/ghci-invocation.html#id307468 
 says that:


"GHCi can also load plain object files (.o or .obj depending on your  
platform) from the command-line. Just add the name the object file to  
the command line."


So, I've tried both of these command lines:
> ghci ./Bar.o -package Foo
> ghci -package Foo ./Bar.o

but ghci still can't find _iceExePath, and the same error occurs.  I'm  
using GHC 6.8.3.  I'm not sure how to proceed and would appreciate any  
advice.


Thanks for your help,
Ryan Wisnesky
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What does it mean that objects are fixpoints? (OO'Haskell)

2009-09-15 Thread Derek Elkins
On Tue, Sep 15, 2009 at 10:14 AM, Manuel Simoni  wrote:
> Hello!
>
> I'm trying to wrap my head around OO'Haskell's notion of objects as fixpoints.
>
> Is OO'Haskell's use of mfix simply a use of something like a monadic
> Y-combinator to give the object access to its own "identity"?

More or less, yes.  To define 'self' or 'this'.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Do I have this right? "Remembering" Memoization!

2009-09-15 Thread Derek Elkins
> But pedantically even the function:
>
>> quux :: Int -> Int
>> quux x = trace "Quux" (bar 12)
>
>> optmain :: IO ()
>> optmain = quux 10 `seq` quux 11 `seq` return ()
>
> might print only once if GHC at the optimization level selected recognizes
> that quux doesn't depend on its argument and rewrote your code with more
> sharing.

Well to be specific, it depends on how you define "function",

quux :: Int -> Int
quux = trace "Quux" bar

will print "Quux" once under the naive semantics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 23:13:59 schrieb Cristiano Paris:
> On Wed, Sep 2, 2009 at 7:16 AM, zaxis  wrote:
> > Isnot it clear without the 'forall' ?
> > data Branch tok st a = Branch (PermParser tok st (b -> a)) (GenParser tok
> > st b)
> >
> > thanks!
>
> I elaborated on this and I wish to add my personal way of figuring out
> what the "forall" keyword means.
>
> When you define:
>
> foo :: a -> a
>
> you are actually defining a _function for every type of a_, which can
> be read: for every a there exists a function foo which can operate on
> it (universal quantification).
>
> When you define something like:
>
> foo :: forall a. a -> a

This is exactly the same type as

foo :: a -> a

(unless you're using ScopedTypeVariables and there's a type variable a in 
scope), since 
type signatures are implicitly forall'd.

>
> you are actually defining a _single_ function which must work for
> every a (that's why we use the "forall" keyword). The difference is
> subtle but the direct consequences of this are: a) that one function
> can't use any information about a apart from the fact that it
> eventually belongs to the type classes specified in the context, b) in
> the case of [a] (or any other type of higher kind, * -> *, * -> * -> *
> and so on) you can mix values of different types.
>
> I hope I haven't written anything wrong :)
>
> Cristiano


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


Re: [Haskell-cafe] Parallel graphics

2009-09-15 Thread namekuseijin
On Tue, Sep 15, 2009 at 8:48 AM, Andrew Coppin
 wrote:
> Using explicit threads has the nice side-effect...

side-effects are bad! ;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 23:00:40 schrieb Cristiano Paris:
> On Tue, Sep 15, 2009 at 10:42 PM, Daniel Fischer
>
>  wrote:
> > 
> > Aaawww.
> > let b' = length b
> > or
> > let b' = foldl' seq () b
> > or
> > let b' = b `using` rnf
> >
> > if you want to force the whole file to be read. But then you should
> > definitely be using ByteStrings.
>
> Yep. But that doesn't solve the original problem of not reading the
> body at all when not needed. Unless using unsafePerformIO.

Yeah, you do *not* want the whole file to be read here, except above for 
testing purposes.
Still, ByteStrings are probably the better choice (if you want the body and 
that can be 
large).

To avoid reading the body without unsafePerformIO:

readBit fn
= Control.Exception.bracket (openFile fn ReadMode) hClose
  (\h -> do
l <- hGetLine h
let i = read l
bdy <- hGetContents h
return $ Bit i bdy)

>
> Cristiano

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


Re: [Haskell-cafe] How to understand the 'forall' ?

2009-09-15 Thread Cristiano Paris
On Wed, Sep 2, 2009 at 7:16 AM, zaxis  wrote:
>
> Isnot it clear without the 'forall' ?
> data Branch tok st a = Branch (PermParser tok st (b -> a)) (GenParser tok st
> b)
>
> thanks!

I elaborated on this and I wish to add my personal way of figuring out
what the "forall" keyword means.

When you define:

foo :: a -> a

you are actually defining a _function for every type of a_, which can
be read: for every a there exists a function foo which can operate on
it (universal quantification).

When you define something like:

foo :: forall a. a -> a

you are actually defining a _single_ function which must work for
every a (that's why we use the "forall" keyword). The difference is
subtle but the direct consequences of this are: a) that one function
can't use any information about a apart from the fact that it
eventually belongs to the type classes specified in the context, b) in
the case of [a] (or any other type of higher kind, * -> *, * -> * -> *
and so on) you can mix values of different types.

I hope I haven't written anything wrong :)

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


Re: [Haskell-cafe] Announce: EnumMap-0.0.1

2009-09-15 Thread Felipe Lessa
On Mon, Sep 14, 2009 at 11:32:04PM -0400, John Van Enk wrote:
> http://hackage.haskell.org/package/EnumMap
>
> Changes pushed. Job Vranish added the SPECIALIZE pragmas, and I believe he
> has more data concerning how much this helps.

Thanks a lot! :)

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:42 PM, Daniel Fischer
 wrote:
> 
> Aaawww.
> let b' = length b
> or
> let b' = foldl' seq () b
> or
> let b' = b `using` rnf
>
> if you want to force the whole file to be read. But then you should 
> definitely be using
> ByteStrings.

Yep. But that doesn't solve the original problem of not reading the
body at all when not needed. Unless using unsafePerformIO.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 22:25:31 schrieb Cristiano Paris:
> On Tue, Sep 15, 2009 at 10:11 PM, Cristiano Paris  wrote:
> > On Tue, Sep 15, 2009 at 10:08 PM, Cristiano Paris  
> > wrote:
> >> ...
> >> So, it seems that "seq b" is completely ineffective and program is not
> >> correct.
> >
> > Correction: removing "seq b" results in nothing being displayed :)
> >
> > So, it's not "completely" effective. I suspect this is related to the
> > fact that a String in Haskell is just a list of Char so we should use
> > seq on every element of b. Let me try...
>
> Now it works as expected:
>
> ---
> module Main where
>
> import System.IO
> import System.IO.Unsafe
> import Control.Applicative
> import Data.List
> import Data.Ord
>
> import Debug.Trace
>
> data Bit = Bit { index :: Integer, body :: String }
>
> readBit fn =
>   withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>= return . read)
> <*> readBody
>   where readBody = trace "In readBody"
>$ withFile fn ReadMode
>  $ \h -> do b <- hGetContents h
> let b' = foldr (\e a -> seq e (a ++ [e])) [] b

Aaawww. 
let b' = length b
or 
let b' = foldl' seq () b
or
let b' = b `using` rnf

if you want to force the whole file to be read. But then you should definitely 
be using 
ByteStrings.

> seq b' $ return $ trace ("Read body from: " ++ fn) b'
>
> main = do bl <- mapM readBit ["file1.txt","file2.txt"]
>   mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
>   putStrLn $ body $ head bl
> 
>
> Two points:
>
> 1 - I had to cut off file1.txt to be just above 1024 bytes otherwise
> the program becomes extremely slow even on a 100KB file with a line
> being output every 5 seconds and with my CPU being completely busy
> (I'm using a modern MacBook Pro).
>
> 2 - Omitting the last line in my program actually causes the body to
> be completely read even if it's not used: this is consistent with my
> hypotesis on seq which now works properly.
>
> :)
>
> Cristiano

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:29 PM, Daniel Fischer
 wrote:
> ...
> It evaluates the String far enough to know whether it's "" or (_:_), that is, 
> to weak head
> normal form. It doesn't look at any character, but it forces at least one 
> character to be
> read from the file.

Yep, the head. That explains why only the first 1024 bytes are read
and displayed...

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


[Haskell-cafe] (weird stuff) Kernel Modules in Haskell ;-)

2009-09-15 Thread Matthias Kilian
A fellow openbsd developer told me the URL below...

I hope this hasn't been posted on this list already (at least I
didn't find it in my local archives):

http://tommd.wordpress.com/2009/09/13/kernel-modules-in-haskell/


Ciao,
Kili

-- 
Logging should be in debug mode only.  If every network driver did
a dmesg printf everytime they came up, would that be a better world?
-- Theo de Raadt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:08 PM, Cristiano Paris  wrote:
> ...
> So, it seems that "seq b" is completely ineffective and program is not 
> correct.

Correction: removing "seq b" results in nothing being displayed :)

So, it's not "completely" effective. I suspect this is related to the
fact that a String in Haskell is just a list of Char so we should use
seq on every element of b. Let me try...

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:29 PM, Daniel Fischer
 wrote:
> Am Dienstag 15 September 2009 21:13:02 schrieb Daniel Fischer:
>> Still, the body should be read lazily.
>> I'm not sure, but the tracing message may be output because of its
>> position.
>>
>> With
>>
>> where
>>     readBody = withFile fn ReadMode $ \h -> do
>>         b <- hGetContents h
>>         seq b $ return (trace ("Read body from: " ++ fn) b)
>>
>> there's no tracing output.
>
> Yes, tested with
> -rw-r--r-- 1 me users 243M 15. Sep 21:17 file1.txt
> -rw-r--r-- 1 me users 243M 15. Sep 21:18 file2.txt

Ok, Daniel, I got the point: the IO action gets performed but there's
no need to use unsafePerformIO as hGetContents is already lazy and the
IO action is "ineffective" anyway when the result is not needed. Yet,
I'm still confused as "seq b" should force the complete execution of
hGetContents. So I decided to run a different test:

I'm using this code:

---
module Main where

import System.IO
import System.IO.Unsafe
import Control.Applicative
import Data.List
import Data.Ord

import Debug.Trace

data Bit = Bit { index :: Integer, body :: String }

readBit fn =
  withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>= return . read)
<*> readBody
  where readBody = trace "In readBody"
   $ withFile fn ReadMode
 $ \h -> do b <- hGetContents h
seq b $ return $ trace ("Read body
from: " ++ fn) b

main = do bl <- mapM readBit ["file1.txt","file2.txt"]
  mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
  putStrLn $ body $ head bl


(Hope this looks better than before).

I ran this on a 115KB-long file1.txt file and traced with dtruss (OSX
strace equivalent). You know what? Only the first 1024 bytes of
file1.txt are read and actually displayed.

So, it seems that "seq b" is completely ineffective and program is not correct.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 22:17:00 schrieb Cristiano Paris:
> On Tue, Sep 15, 2009 at 10:12 PM, Ross Mellgren  wrote:
> > Wouldn't seq b only force (at minimum) the first character of the file?
>
> I think it force the evaluation of the "Cons" in the String but not
> the characters therein.

It evaluates the String far enough to know whether it's "" or (_:_), that is, 
to weak head 
normal form. It doesn't look at any character, but it forces at least one 
character to be 
read from the file.

>
> Cristiano

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:25 PM, Cristiano Paris  wrote:
> ...
> Two points:
>
> 1 - I had to cut off file1.txt to be just above 1024 bytes otherwise
> the program becomes extremely slow even on a 100KB file with a line
> being output every 5 seconds and with my CPU being completely busy
> (I'm using a modern MacBook Pro).

GC in charge here. Using "foldl" resolves the problem. Maybe too many
thunks are being created on the stack...

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:20 PM, Ross Mellgren  wrote:
> Ack, IGNORE ME! Way too strict.

Oh, well, I used foldr+seq to achieve the same result... I think, but
I think that, if this is the solution, I'll use rnf as I did on other
occasions.

Thanks.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:11 PM, Cristiano Paris  wrote:
> On Tue, Sep 15, 2009 at 10:08 PM, Cristiano Paris  wrote:
>> ...
>> So, it seems that "seq b" is completely ineffective and program is not 
>> correct.
>
> Correction: removing "seq b" results in nothing being displayed :)
>
> So, it's not "completely" effective. I suspect this is related to the
> fact that a String in Haskell is just a list of Char so we should use
> seq on every element of b. Let me try...

Now it works as expected:

---
module Main where

import System.IO
import System.IO.Unsafe
import Control.Applicative
import Data.List
import Data.Ord

import Debug.Trace

data Bit = Bit { index :: Integer, body :: String }

readBit fn =
  withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>= return . read)
<*> readBody
  where readBody = trace "In readBody"
   $ withFile fn ReadMode
 $ \h -> do b <- hGetContents h
let b' = foldr (\e a -> seq e (a ++ [e])) [] b
seq b' $ return $ trace ("Read body
from: " ++ fn) b'

main = do bl <- mapM readBit ["file1.txt","file2.txt"]
  mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
  putStrLn $ body $ head bl


Two points:

1 - I had to cut off file1.txt to be just above 1024 bytes otherwise
the program becomes extremely slow even on a 100KB file with a line
being output every 5 seconds and with my CPU being completely busy
(I'm using a modern MacBook Pro).

2 - Omitting the last line in my program actually causes the body to
be completely read even if it's not used: this is consistent with my
hypotesis on seq which now works properly.

:)

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


Re: [Haskell-cafe] Parallel graphics

2009-09-15 Thread Edward Kmett
Block, line or 'beam' decomposition tends to work well for raytracing tasks,
because they tend to give you a good cache locality and don't create a
ridiculous explosion of parallel jobs.

You'll need to do some tuning to figure out the right granularity for the
decomposition. But typically a few hundred tasks works a lot better than
tens of thousands or millions. You need to balance the tension between
having too much overhead maintaining the decomposition with wasted work from
lumpy task completion times and coarse grain sizes.

Unfortunately, using Haskell it is hard to do what you can do, say, in C++
with Intel Thread Building Blocks to get a self-tuning decomposition of your
range, which self-tunes by splitting stolen tasks. You don't get the same
visibility into whether or not the task you are doing was stolen from
elsewhere when using GHC's sparks.

-Edward Kmett

On Tue, Sep 15, 2009 at 7:48 AM, Andrew Coppin
wrote:

> I have a number of compute-bound graphics programs written in Haskell.
> (Fractal generators, ray tracers, that kind of thing.) GHC offers several
> concurrency and parallelism abstractions, but what's the best way to use
> these to get images rendered as fast as possible, using the available
> compute power?
>
> (OK, well the *best* way is to use the GPU. But AFAIK that's still a
> theoretical research project, so we'll leave that for now.)
>
> I've identified a couple of common cases. You have a 2D grid of points, and
> you want to compute the value at each point. Eventually you will have a grid
> of *pixels* where each value is a *colour*, but there may be intermediate
> steps before that. So, what cases exist?
>
> 1. A point's value is a function of its coordinates.
>
> 2. A point's value is a function of its previous value from the last frame.
>
> 3. A point's value is a function of *several* points from the last frame.
>
> How can we accelerate this? I see a few options:
>
> - Create a spark for every point in the grid.
> - Create several explicit threads to populate non-overlapping regions of
> the grid.
> - Use parallel arrays. (Does this actually works yet??)
>
> I'm presuming that sparking every individual point is going to create
> billions of absolutely tiny sparks, which probably won't give great
> performance. We could spark every line rather than every point?
>
> Using explicit threads has the nice side-effect that we can produce
> progress information. Few things are more frustrating than staring at a
> blank screen with no idea how long it's going to take. I'm thinking this
> method might also allow you to avoid two cores tripping over each other's
> caches.
>
> And then there's parallel arrays, which presumably are designed from the
> ground up for exactly this type of task. But are they usable yet?
>
> Any further options?
>
>
> ___
> 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] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Ross Mellgren

Ack, IGNORE ME! Way too strict.

-Ross

On Sep 15, 2009, at 4:20 PM, Ross Mellgren wrote:


Ah yeah, that too. Control.Parallel.Strategies.rnf to the rescue?

-Ross

On Sep 15, 2009, at 4:17 PM, Cristiano Paris wrote:

On Tue, Sep 15, 2009 at 10:12 PM, Ross Mellgren hask...@z.odi.ac> wrote:
Wouldn't seq b only force (at minimum) the first character of the  
file?


I think it force the evaluation of the "Cons" in the String but not
the characters therein.

Cristiano




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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Ross Mellgren

Ah yeah, that too. Control.Parallel.Strategies.rnf to the rescue?

-Ross

On Sep 15, 2009, at 4:17 PM, Cristiano Paris wrote:

On Tue, Sep 15, 2009 at 10:12 PM, Ross Mellgren hask...@z.odi.ac> wrote:
Wouldn't seq b only force (at minimum) the first character of the  
file?


I think it force the evaluation of the "Cons" in the String but not
the characters therein.

Cristiano


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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 10:12 PM, Ross Mellgren  wrote:
> Wouldn't seq b only force (at minimum) the first character of the file?

I think it force the evaluation of the "Cons" in the String but not
the characters therein.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Ross Mellgren

Wouldn't seq b only force (at minimum) the first character of the file?

-Ross

On Sep 15, 2009, at 4:08 PM, Cristiano Paris wrote:


On Tue, Sep 15, 2009 at 9:29 PM, Daniel Fischer
 wrote:

Am Dienstag 15 September 2009 21:13:02 schrieb Daniel Fischer:

Still, the body should be read lazily.
I'm not sure, but the tracing message may be output because of its
position.

With

where
readBody = withFile fn ReadMode $ \h -> do
b <- hGetContents h
seq b $ return (trace ("Read body from: " ++ fn) b)

there's no tracing output.


Yes, tested with
-rw-r--r-- 1 me users 243M 15. Sep 21:17 file1.txt
-rw-r--r-- 1 me users 243M 15. Sep 21:18 file2.txt


Ok, Daniel, I got the point: the IO action gets performed but there's
no need to use unsafePerformIO as hGetContents is already lazy and the
IO action is "ineffective" anyway when the result is not needed. Yet,
I'm still confused as "seq b" should force the complete execution of
hGetContents. So I decided to run a different test:

I'm using this code:

---
module Main where

import System.IO
import System.IO.Unsafe
import Control.Applicative
import Data.List
import Data.Ord

import Debug.Trace

data Bit = Bit { index :: Integer, body :: String }

readBit fn =
 withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>= return . read)
<*> readBody
 where readBody = trace "In readBody"
  $ withFile fn ReadMode
$ \h -> do b <- hGetContents h
   seq b $ return $ trace ("Read body
from: " ++ fn) b

main = do bl <- mapM readBit ["file1.txt","file2.txt"]
 mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
 putStrLn $ body $ head bl


(Hope this looks better than before).

I ran this on a 115KB-long file1.txt file and traced with dtruss (OSX
strace equivalent). You know what? Only the first 1024 bytes of
file1.txt are read and actually displayed.

So, it seems that "seq b" is completely ineffective and program is  
not correct.


Cristiano
___
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] Do I have this right? "Remembering" Memoization!

2009-09-15 Thread Edward Kmett
I agree with what you meant, but not quite with what you said. To be
pedantic:

> import Debug.Trace

> foo :: Int
> foo = trace "Foo" (bar 12)

> bar :: Int -> Int
> bar x = trace "Bar" x

> main :: IO ()
> main = foo `seq` foo `seq` return ()

main prints "Foo\nBar\n" showing that the bar is only evaluated once,
because foo is already evaluated, even though it is referenced twice. So
attempting to evaluate foo again just returns the same result.

 > baz :: Int -> Int
> baz x = trace "Baz" (bar x)

> correct :: IO ()
> correct = baz 10 `seq` baz 11 `seq` return ()

Though, as you said, call, you probably meant foo was a
function, and correct prints "Baz\nBar\nBaz\nBar\n" like you had indicated.

But pedantically even the function:

> quux :: Int -> Int
> quux x = trace "Quux" (bar 12)
> optmain :: IO ()
> optmain = quux 10 `seq` quux 11 `seq` return ()

might print only once if GHC at the optimization level selected recognizes
that quux doesn't depend on its argument and rewrote your code with more
sharing.

-Edward Kmett

On Sun, Sep 13, 2009 at 7:45 PM, Mark Wotton  wrote:

>
> On 14/09/2009, at 9:28 AM, Casey Hawthorne wrote:
>
> Do I have this right?  "Remembering"  Memoization!
>>
>> For some applications, a lot of state does not to be saved, since
>> "initialization" functions can be called early, and these functions
>> will "remember" - (memoize) their results when called again, because
>> of lazy evaluation?
>>
>
> You don't get memoisation for free.
> If you define a variable once in a where block, it's true that you'll
> evaluate it at most once, but if you repeatedly call a function "foo" that
> then calls "bar 12" each time, "bar 12" will be evaluated once per "foo"
> call.
>
> Cheers
> Mark
>
> ___
> 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] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:39 PM, Svein Ove Aas  wrote:
> As a general sort of warning, do not use hGetContents (or lazy i/o, in
> general) in combination with withFile.
>
> withFile closes the handle when the program lexically exits its scope.
> However, when using hGetContents, the file contents will not be read
> until after you do this, and will therefore fail to be read at all;
> I'm not sure whether this will produce a truncated string or an
> exception.

A truncated string. I already encountered such a scenario.

> Instead, use openFile directly. Handles have (ISTR) finalizers on
> them, and so should be automatically closed if you lose hold of one..
> eventually. getContents of course closes it once it hits EOF, but that
> isn't exactly reliable.
>
> If that isn't satisfactory, use strict I/O. It's less convenient, but
> it's also easier to reason about.

Thank you.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Svein Ove Aas
As a general sort of warning, do not use hGetContents (or lazy i/o, in
general) in combination with withFile.

withFile closes the handle when the program lexically exits its scope.
However, when using hGetContents, the file contents will not be read
until after you do this, and will therefore fail to be read at all;
I'm not sure whether this will produce a truncated string or an
exception.

Instead, use openFile directly. Handles have (ISTR) finalizers on
them, and so should be automatically closed if you lose hold of one..
eventually. getContents of course closes it once it hits EOF, but that
isn't exactly reliable.

If that isn't satisfactory, use strict I/O. It's less convenient, but
it's also easier to reason about.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:16 PM, Svein Ove Aas  wrote:
> I have a number of suggestions, some of which conflict with each
> other, so I'll just throw them out here. Let's see..

:)

> First off, the IO monad does indeed enforce sequencing; that's its
> primary purpose.

So, unsafePerformIO can be thought as an escape to this strict rule.

> However, you can ask for it to run I/O out of order,
> specifically when the value the out-of-order action returns is
> actually forced (used); that's lazy I/O, and is implemented using
> unsafeInterleaveIO.

I imagined that. But I hate to have to use unsafePerformIO when
hGetContets is already using it.

> You would not usually use unsafeInterleaveIO directly, though.

That's the point.

> Instead, you'd use an existing wrapper, such as hGetContents. (for
> Strings, or lazy bytestrings; the strict bytestring variant reasonably
> has a strict semantics)
>
> One thing to keep in mind about lazy I/O is that the I/O in question
> can run at any arbitrary time, or not at all; not more than once,
> though. You must make sure this is safe. For file input, that
> basically means the file should not change during the program's
> lifetime.

Ok.

> hGetLine is not lazy in this way, but the hGetContents you use is. I'm
> not sure whether this means your program should work as-is, and I'm
> not going to examine it closely enough to tell - as you mentioned it's
> a mockup anyway. Besides..
>
> Strings are also *slow*. What you want for I/O is, when reasonably
> possible, bytestrings. You'd then use parsec-bytestring, or if
> possible Data.Binary, to parse said bytestring; the latter is faster
> (..probably), if more limited in function.

Yes, that was only a first attempt, kind of prototype...

> You could use the lazy bytestring hGetContents for this. However...
>
> There is also a bytestring-mmap package on hackage, which outsources
> the decision of what blocks to load into memory to the OS, and has the
> best performance overall. Use this.
>
>
> Oh. And unsafePerformIO is a trap that will kill you. See
> http://www.girlgeniusonline.com/comic.php?date=20070725 for details.

Thank you for the link.

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 21:13:02 schrieb Daniel Fischer:
> Still, the body should be read lazily.
> I'm not sure, but the tracing message may be output because of its
> position.
>
> With
>
> where
>     readBody = withFile fn ReadMode $ \h -> do
>         b <- hGetContents h
>         seq b $ return (trace ("Read body from: " ++ fn) b)
>
> there's no tracing output.

Yes, tested with 
-rw-r--r-- 1 me users 243M 15. Sep 21:17 file1.txt
-rw-r--r-- 1 me users 243M 15. Sep 21:18 file2.txt

original:

./cparis2 +RTS -Sstderr
AllocCopied LiveGCGC TOT TOT  Page Flts
bytes bytes bytes  user  elapuserelap  
Read body: file1.txt   
Read body: file2.txt   
2  
3  
   427996  1408 18620  0.00  0.000.000.0000  (Gen:  1)
 4096  0.00  0.00 

 432,092 bytes allocated in the heap
   1,408 bytes copied during GC 
  18,620 bytes maximum residency (1 sample(s))
  22,340 bytes maximum slop   
   1 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0: 0 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.00s  (  0.00s elapsed)
  GCtime0.00s  (  0.00s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.00s  (  0.00s elapsed)

  %GC time   0.0%  (8.3% elapsed)

  Alloc rate432,092,000,000 bytes per MUT second

  Productivity 100.0% of total user, 0.1% of total elapsed

moved trace:

./CParis +RTS -Sstderr
AllocCopied LiveGCGC TOT TOT  Page Flts
bytes bytes bytes  user  elapuserelap
2
3
   426100  1408 18476  0.00  0.000.000.0000  (Gen:  1)
 4096  0.00  0.00

 430,196 bytes allocated in the heap
   1,408 bytes copied during GC
  18,476 bytes maximum residency (1 sample(s))
  22,484 bytes maximum slop
   1 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0: 0 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.00s  (  0.00s elapsed)
  GCtime0.00s  (  0.00s elapsed)
  EXIT  time0.00s  (  0.00s elapsed)
  Total time0.00s  (  0.00s elapsed)

  %GC time   0.0%  (9.3% elapsed)

  Alloc rate107,549,000 bytes per MUT second

  Productivity 100.0% of total user, 230.3% of total elapsed

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
On Tue, Sep 15, 2009 at 9:13 PM, Daniel Fischer
 wrote:
> ...
> Still, the body should be read lazily.
> I'm not sure, but the tracing message may be output because of its position.
>
> With
>
> where
>    readBody = withFile fn ReadMode $ \h -> do
>        b <- hGetContents h
>        seq b $ return (trace ("Read body from: " ++ fn) b)
>
> there's no tracing output.

Impressive as I can't spot the difference. But my question is: is the
chunk of data actually read or not? Consider the following code:


readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>=
return . read) <*> readBody
 where readBody = trace "In readBody"
  $ withFile fn ReadMode
$ \h -> do b <- hGetContents h
   seq b $ return $ trace
("Read body from: " ++ fn) b


The message "In readBody" gets written, while "Read body from..."
don't. So? I think that the IO action is actually performed but the
result is simply discarded. Am I right?

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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Svein Ove Aas
I have a number of suggestions, some of which conflict with each
other, so I'll just throw them out here. Let's see..

First off, the IO monad does indeed enforce sequencing; that's its
primary purpose. However, you can ask for it to run I/O out of order,
specifically when the value the out-of-order action returns is
actually forced (used); that's lazy I/O, and is implemented using
unsafeInterleaveIO.

You would not usually use unsafeInterleaveIO directly, though.
Instead, you'd use an existing wrapper, such as hGetContents. (for
Strings, or lazy bytestrings; the strict bytestring variant reasonably
has a strict semantics)

One thing to keep in mind about lazy I/O is that the I/O in question
can run at any arbitrary time, or not at all; not more than once,
though. You must make sure this is safe. For file input, that
basically means the file should not change during the program's
lifetime.

hGetLine is not lazy in this way, but the hGetContents you use is. I'm
not sure whether this means your program should work as-is, and I'm
not going to examine it closely enough to tell - as you mentioned it's
a mockup anyway. Besides..

Strings are also *slow*. What you want for I/O is, when reasonably
possible, bytestrings. You'd then use parsec-bytestring, or if
possible Data.Binary, to parse said bytestring; the latter is faster
(..probably), if more limited in function.

You could use the lazy bytestring hGetContents for this. However...

There is also a bytestring-mmap package on hackage, which outsources
the decision of what blocks to load into memory to the OS, and has the
best performance overall. Use this.


Oh. And unsafePerformIO is a trap that will kill you. See
http://www.girlgeniusonline.com/comic.php?date=20070725 for details.

On Tue, Sep 15, 2009 at 8:36 PM, Cristiano Paris
 wrote:
> Hi Cafè,
>
> I've the following problem: I have a (possibly very long) list of
> files on disk. Each file contains some metadata at the beginning and
> continues with a (possibly very large) chunk of data.
>
> Now, the program I'm writing can be run in two modes: either read a
> specific file from the disk and show the whole chunk of data on
> screen, or read all the files' metadata, sort the file list based on
> the metadata, and display a summary of those without reading the chunk
> of data from each file. I've factored out the file access machinery in
> a single module so as to use it indifferently under the two scenarios.
>
> At first, I wrote a piece of code which, in spirit, works like the
> following reduced case:
>
> --
> module Main where
>
> import System.IO
> import Control.Applicative
> import Data.List
> import Data.Ord
>
> import Debug.Trace
>
> data Bit = Bit { index :: Integer, body :: String }
>
> readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>=
> return . read) <*> readBody
>             where readBody = withFile fn ReadMode $ \h -> do b <-
> hGetContents h
>                                                              seq b $
> trace ("Read body from: " ++ fn) $ return b
>
> main = do bl <- mapM readBit ["file1.txt","file2.txt"]
>          mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
> 
>
> which is very expressive as it's written in applicative style.
>
> Each file is like the following:
>
>  file1.txt 
> 1
> foo
> 
>
> I've created a separate IO action for reading the body in the hope
> that it wouldn't get executed when the file list is sorted. But, to my
> surprise, it didn't work as the trace message gets written for each
> file before the summary is displayed.
>
> Thinking about this, I came to the conclusion that the IO Monad is
> enforcing proper IO ordering so that the IO action for file1's body
> must be executed right before IO action for file2's index one.
>
> If this is true, the only solution that came into my mind was to wrap
> the IO action for reading the body in an unsafePerformIO call. I
> actually ran the program with this modification and it works properly.
>
> So, as using unsafePerformIO is a Great Evil (TM), I'm wondering if
> there's a different way to do this which doesn't rely on retyping body
> as an IO action returning a String, which would break my pure code
> manipulating the files.
>
> My opinion is that using unsafePerformIO here is like ensuring the
> compiler that there're no observable side effects in running the IO
> action for reading the body and that no other side effects would
> impact this IO action.
>
> Thank you for any thoughts.
>
> Cristiano
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



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


Re: [Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Daniel Fischer
Am Dienstag 15 September 2009 20:36:06 schrieb Cristiano Paris:
> Hi Cafè,
>
> I've the following problem: I have a (possibly very long) list of
> files on disk. Each file contains some metadata at the beginning and
> continues with a (possibly very large) chunk of data.
>
> Now, the program I'm writing can be run in two modes: either read a
> specific file from the disk and show the whole chunk of data on
> screen, or read all the files' metadata, sort the file list based on
> the metadata, and display a summary of those without reading the chunk
> of data from each file. I've factored out the file access machinery in
> a single module so as to use it indifferently under the two scenarios.
>
> At first, I wrote a piece of code which, in spirit, works like the
> following reduced case:
>
> --
> module Main where
>
> import System.IO
> import Control.Applicative
> import Data.List
> import Data.Ord
>
> import Debug.Trace
>
> data Bit = Bit { index :: Integer, body :: String }
>
> readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>=
> return . read) <*> readBody
>  where readBody = withFile fn ReadMode $ \h -> do b <-
> hGetContents h
>   seq b $
> trace ("Read body from: " ++ fn) $ return b

Still, the body should be read lazily.
I'm not sure, but the tracing message may be output because of its position.

With

where
readBody = withFile fn ReadMode $ \h -> do
b <- hGetContents h
seq b $ return (trace ("Read body from: " ++ fn) b)

there's no tracing output.
>
> main = do bl <- mapM readBit ["file1.txt","file2.txt"]
>   mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl
> 
>
> which is very expressive as it's written in applicative style.
>
> Each file is like the following:
>
>  file1.txt 
> 1
> foo
> 
>
> I've created a separate IO action for reading the body in the hope
> that it wouldn't get executed when the file list is sorted. But, to my
> surprise, it didn't work as the trace message gets written for each
> file before the summary is displayed.
>
> Thinking about this, I came to the conclusion that the IO Monad is
> enforcing proper IO ordering so that the IO action for file1's body
> must be executed right before IO action for file2's index one.
>
> If this is true, the only solution that came into my mind was to wrap
> the IO action for reading the body in an unsafePerformIO call. I
> actually ran the program with this modification and it works properly.
>
> So, as using unsafePerformIO is a Great Evil (TM), I'm wondering if
> there's a different way to do this which doesn't rely on retyping body
> as an IO action returning a String, which would break my pure code
> manipulating the files.
>
> My opinion is that using unsafePerformIO here is like ensuring the
> compiler that there're no observable side effects in running the IO
> action for reading the body and that no other side effects would
> impact this IO action.
>
> Thank you for any thoughts.
>
> Cristiano


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


[Haskell-cafe] Is it safe to use unsafePerformIO here?

2009-09-15 Thread Cristiano Paris
Hi Cafè,

I've the following problem: I have a (possibly very long) list of
files on disk. Each file contains some metadata at the beginning and
continues with a (possibly very large) chunk of data.

Now, the program I'm writing can be run in two modes: either read a
specific file from the disk and show the whole chunk of data on
screen, or read all the files' metadata, sort the file list based on
the metadata, and display a summary of those without reading the chunk
of data from each file. I've factored out the file access machinery in
a single module so as to use it indifferently under the two scenarios.

At first, I wrote a piece of code which, in spirit, works like the
following reduced case:

--
module Main where

import System.IO
import Control.Applicative
import Data.List
import Data.Ord

import Debug.Trace

data Bit = Bit { index :: Integer, body :: String }

readBit fn = withFile fn ReadMode $ \h -> Bit <$> (hGetLine h >>=
return . read) <*> readBody
 where readBody = withFile fn ReadMode $ \h -> do b <-
hGetContents h
  seq b $
trace ("Read body from: " ++ fn) $ return b

main = do bl <- mapM readBit ["file1.txt","file2.txt"]
  mapM_ (putStrLn . show . index) $ sortBy (comparing index) bl


which is very expressive as it's written in applicative style.

Each file is like the following:

 file1.txt 
1
foo


I've created a separate IO action for reading the body in the hope
that it wouldn't get executed when the file list is sorted. But, to my
surprise, it didn't work as the trace message gets written for each
file before the summary is displayed.

Thinking about this, I came to the conclusion that the IO Monad is
enforcing proper IO ordering so that the IO action for file1's body
must be executed right before IO action for file2's index one.

If this is true, the only solution that came into my mind was to wrap
the IO action for reading the body in an unsafePerformIO call. I
actually ran the program with this modification and it works properly.

So, as using unsafePerformIO is a Great Evil (TM), I'm wondering if
there's a different way to do this which doesn't rely on retyping body
as an IO action returning a String, which would break my pure code
manipulating the files.

My opinion is that using unsafePerformIO here is like ensuring the
compiler that there're no observable side effects in running the IO
action for reading the body and that no other side effects would
impact this IO action.

Thank you for any thoughts.

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


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
Thanks for explanation Sean!

On Tue, Sep 15, 2009 at 4:30 PM, Sean Leather  wrote:

>
>
>> "Existential types" sounds a bit scary :)
>>
>>>
> It's unfortunate that they've developed a scariness feeling associated with
> them. They can be used in strange ways, but simple uses are quite
> approachable. One way to think of them is like implementing an
> object-oriented interface. You know it's an object, but you can't do
> anything with it except use the methods of the interface.
>
> ---
>
> {-# LANGUAGE ExistentialQuantification #-}
>
> data Square = Square ...
> data Circle = Circle ...
>
> class Perimeter a where perimeter :: a -> Double
> instance Perimeter Square where perimeter (Square ...) = ...
> instance Perimeter Circle where perimeter (Circle ...) = ...
>
> -- The 'a' is hidden here. The interface is defined by the class
> constraint.
> data Perimeterizable = forall a . (Perimeter a) => P a
>
> -- This is the accessor method for things Perimeterizable.
> getPerimeter (P x) = perimeter x
>
> vals :: [Perimeterizable]
> vals = [P Square, P Circle]
>
> perims = map getPerimeter vals
>
> ---
>
> Regards,
> Sean
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What does it mean that objects are fixpoints? (OO'Haskell)

2009-09-15 Thread Sean Leather
> I'm trying to wrap my head around OO'Haskell's notion of objects as
> fixpoints.
>
> Is OO'Haskell's use of mfix simply a use of something like a monadic
> Y-combinator to give the object access to its own "identity"?
>

I don't remember the details exactly, but isn't it to support open recursion
for inherited/overridden methods?

http://etymon.blogspot.com/2006/04/open-recursion-definition.html

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


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Sean Leather
> "Existential types" sounds a bit scary :)
>
>>
It's unfortunate that they've developed a scariness feeling associated with
them. They can be used in strange ways, but simple uses are quite
approachable. One way to think of them is like implementing an
object-oriented interface. You know it's an object, but you can't do
anything with it except use the methods of the interface.

---

{-# LANGUAGE ExistentialQuantification #-}

data Square = Square ...
data Circle = Circle ...

class Perimeter a where perimeter :: a -> Double
instance Perimeter Square where perimeter (Square ...) = ...
instance Perimeter Circle where perimeter (Circle ...) = ...

-- The 'a' is hidden here. The interface is defined by the class constraint.
data Perimeterizable = forall a . (Perimeter a) => P a

-- This is the accessor method for things Perimeterizable.
getPerimeter (P x) = perimeter x

vals :: [Perimeterizable]
vals = [P Square, P Circle]

perims = map getPerimeter vals

---

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


[Haskell-cafe] What does it mean that objects are fixpoints? (OO'Haskell)

2009-09-15 Thread Manuel Simoni
Hello!

I'm trying to wrap my head around OO'Haskell's notion of objects as fixpoints.

Is OO'Haskell's use of mfix simply a use of something like a monadic
Y-combinator to give the object access to its own "identity"?

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


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
It's hard to say what really is 2d or 3d. Think about closed 3d curve
(points placed in 3d space somehow). Is it 2d or 3d? Depends on the
interpretation.
Usually DCC packages don't care about this. And I wouldn't too :p Who needs
extra level of complexity without any reason?

On Tue, Sep 15, 2009 at 3:48 PM, Tom Nielsen  wrote:

> I think you are in trouble because you have mixed 2D and 3D shapes in
> one data type.
>
> --not checked for typos, syntax, idiocy etc.
> {-# LANGUAGE GADTs #-}
>
> data Z
> data S n
>
> type Two = S (S Z)
> type Three = S Two
>
> data Geometry dims where
>Sphere :: Position -> Radius -> Geometry Three
>Cylinder :: Position -> Radius -> Height -> Geometry Three
>Circle :: Position -> Radius -> Geometry Two
>
>Postcard :: Position -> Orientation -> Geometry Two -> Geometry Three
>
> perimeter :: Geometry Two -> Double
> perimeter (Circle _ r) = 2*pi*r
>
> Tom
>
> On Tue, Sep 15, 2009 at 11:29 AM, Olex P  wrote:
> > Hey guys,
> >
> > It's a dumb question but I'd like to know a right answer...
> > Let's say we have some geometry data that can be Sphere, Cylinder, Circle
> > and so on. We can implement it as new data type plus a bunch of functions
> > that work on this data:
> >
> > data Geometry = Sphere Position Radius
> > | Cylinder Position Radius Height
> > | Circle Position Radius
> > deriving (Show)
> >
> > perimeter (Sphere _ r) = 0.0
> > perimeter (Cylinder _ r h) = 0.0
> > perimeter (Circle _ r) = 2.0 * pi * r
> >
> > Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
> > type class for objects that have perimeter and make an instance of it
> only
> > for Circle (data Circle = Circle Position Radius). Make sense. But these
> > three functions above have desired behaviour. If user has a list of
> objects
> > like [Sphere, Circle, Circle, Cylinder] he would like to calculate
> > perimeters of each object using map perimerer list (in this case we also
> > have to modify Geometry data type).
> > So we could make instances of "perimeter" type class for all objects and
> > return zero in case if perimeter doesn't make sense.
> > Same as previous version but with typeclasses and with additional
> > constructors (constructors for each type of object + constructors in
> > Geometry data). Looks a bit overcomplicated.
> > Any reasons to use type classes in this case? Maybe there is something
> I'm
> > missing?
> >
> > Cheers,
> > -O
> >
> > ___
> > 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] Typeclasses vs simple functions?

2009-09-15 Thread Tom Nielsen
I think you are in trouble because you have mixed 2D and 3D shapes in
one data type.

--not checked for typos, syntax, idiocy etc.
{-# LANGUAGE GADTs #-}

data Z
data S n

type Two = S (S Z)
type Three = S Two

data Geometry dims where
Sphere :: Position -> Radius -> Geometry Three
Cylinder :: Position -> Radius -> Height -> Geometry Three
Circle :: Position -> Radius -> Geometry Two

Postcard :: Position -> Orientation -> Geometry Two -> Geometry Three

perimeter :: Geometry Two -> Double
perimeter (Circle _ r) = 2*pi*r

Tom

On Tue, Sep 15, 2009 at 11:29 AM, Olex P  wrote:
> Hey guys,
>
> It's a dumb question but I'd like to know a right answer...
> Let's say we have some geometry data that can be Sphere, Cylinder, Circle
> and so on. We can implement it as new data type plus a bunch of functions
> that work on this data:
>
> data Geometry = Sphere Position Radius
>                         | Cylinder Position Radius Height
>                         | Circle Position Radius
>     deriving (Show)
>
> perimeter (Sphere _ r) = 0.0
> perimeter (Cylinder _ r h) = 0.0
> perimeter (Circle _ r) = 2.0 * pi * r
>
> Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
> type class for objects that have perimeter and make an instance of it only
> for Circle (data Circle = Circle Position Radius). Make sense. But these
> three functions above have desired behaviour. If user has a list of objects
> like [Sphere, Circle, Circle, Cylinder] he would like to calculate
> perimeters of each object using map perimerer list (in this case we also
> have to modify Geometry data type).
> So we could make instances of "perimeter" type class for all objects and
> return zero in case if perimeter doesn't make sense.
> Same as previous version but with typeclasses and with additional
> constructors (constructors for each type of object + constructors in
> Geometry data). Looks a bit overcomplicated.
> Any reasons to use type classes in this case? Maybe there is something I'm
> missing?
>
> Cheers,
> -O
>
> ___
> 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] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
Cool. It's more and more clear guys.
Thanks a lot. I'll check that "expression problem".
"Existential types" sounds a bit scary :)


On Tue, Sep 15, 2009 at 3:26 PM, Sean Leather  wrote:

>
>
>> Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
>> type class for objects that have perimeter and make an instance of it only
>> for Circle (data Circle = Circle Position Radius). Make sense. But these
>> three functions above have desired behaviour. If user has a list of objects
>> like [Sphere, Circle, Circle, Cylinder] he would like to calculate
>> perimeters of each object using map perimerer list (in this case we also
>> have to modify Geometry data type).
>> So we could make instances of "perimeter" type class for all objects and
>> return zero in case if perimeter doesn't make sense.
>> Same as previous version but with typeclasses and with additional
>> constructors (constructors for each type of object + constructors in
>> Geometry data). Looks a bit overcomplicated.
>> Any reasons to use type classes in this case? Maybe there is something I'm
>> missing?
>>
>
> If you're talking about a single datatype with multiple constructors, then
> the function 'perimeter :: Geometry -> Maybe Double' makes sense. If you're
> talking about multiple datatypes, then you probably want to go type class
> route.
>
> data Sphere = Sphere ...
> data Circle = Circle ...
>
> class Perimeter a where perimeter :: a -> Double
> instance Perimeter Circle where perimeter (Circle ...) = ...
> -- No instance for Sphere
>
> class Volume a where volume :: a -> Double
> instance Volume Sphere where volume (Sphere ...) = ...
> -- No instance for Circle
>
> You have to decide whether (1) a datatype Geometry makes sense or (2) a
> datatype per geometric entity is better. One advantage to #1 is that writing
> functions over the datatype is easy. One advantage to #2 is that you have
> fewer (partial) 'Maybe' functions. This is also related to the "expression
> problem," a Googleable term.
>
> As for having a list of objects, you can do it with either approach. The
> second approach may require existential types.
>
> Regards,
> Sean
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Sean Leather
> Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
> type class for objects that have perimeter and make an instance of it only
> for Circle (data Circle = Circle Position Radius). Make sense. But these
> three functions above have desired behaviour. If user has a list of objects
> like [Sphere, Circle, Circle, Cylinder] he would like to calculate
> perimeters of each object using map perimerer list (in this case we also
> have to modify Geometry data type).
> So we could make instances of "perimeter" type class for all objects and
> return zero in case if perimeter doesn't make sense.
> Same as previous version but with typeclasses and with additional
> constructors (constructors for each type of object + constructors in
> Geometry data). Looks a bit overcomplicated.
> Any reasons to use type classes in this case? Maybe there is something I'm
> missing?
>

If you're talking about a single datatype with multiple constructors, then
the function 'perimeter :: Geometry -> Maybe Double' makes sense. If you're
talking about multiple datatypes, then you probably want to go type class
route.

data Sphere = Sphere ...
data Circle = Circle ...

class Perimeter a where perimeter :: a -> Double
instance Perimeter Circle where perimeter (Circle ...) = ...
-- No instance for Sphere

class Volume a where volume :: a -> Double
instance Volume Sphere where volume (Sphere ...) = ...
-- No instance for Circle

You have to decide whether (1) a datatype Geometry makes sense or (2) a
datatype per geometric entity is better. One advantage to #1 is that writing
functions over the datatype is easy. One advantage to #2 is that you have
fewer (partial) 'Maybe' functions. This is also related to the "expression
problem," a Googleable term.

As for having a list of objects, you can do it with either approach. The
second approach may require existential types.

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


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread John Dorsey
> perimeter :: Geometry -> Double
> perimeter (Sphere _ r) = 0.0
> perimeter (Circle _ r) = 2.0 * pi * r
> 
> The latter is even simpler because there is no need in extraction of Double
> value from Maybe.

I'd strongly advise against this last one on style grounds.  (0 :: Double)
isn't nearly as suitable as a distinguished value indicating an invalid
result as Nothing.  It can be made to work, in the same way that you can
write complex code in asm; instead, use a solution that gives you
type-level help in getting it right.  I'd use Maybe.

Regards,
John

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


[Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Lyndon Maydwell
-- Forwarded message --
From: Lyndon Maydwell 
Date: Tue, Sep 15, 2009 at 10:03 PM
Subject: Re: [Haskell-cafe] Typeclasses vs simple functions?
To: Olex P 


I think it depends on what is going to be using the functions, data.
As far as I can tell, type classes seem to be used in code designed
for reuse. So if it is just for a small part of a project that is
hidden behind an interface or something, then it's probably fine to
just use data/functions without type classes.

Keep in mind that these are the musings of someone who only recently
began using Haskell. If someone else has a better explanation, then
I'd be interested as well :)

On Tue, Sep 15, 2009 at 9:57 PM, Olex P  wrote:
> Well... How this:
>
> instance Encircled Geometry where
>        perimeter (Sphere _ r) = Nothing
>        perimeter (Circle _ r) = Just $ 2.0 * pi * r
>
> differs from this:
>
> perimeter :: Geometry -> Maybe Double
> perimeter (Sphere _ r) = Nothing
> perimeter (Circle _ r) = Just $ 2.0 * pi * r
>
> and from this:
>
> perimeter :: Geometry -> Double
> perimeter (Sphere _ r) = 0.0
> perimeter (Circle _ r) = 2.0 * pi * r
>
> The latter is even simpler because there is no need in extraction of Double
> value from Maybe.
> So the question is still there: do I need a type class?
>
> On Tue, Sep 15, 2009 at 12:21 PM, Olex P  wrote:
>>
>> Sure! I completely forgot about Maybe. The only one question is is it good
>> from the point of view of ordinary user who doesn't know about such things
>> like functional programming, monads etc. Imagine average user who is looking
>> into a spreadsheet and sees values 0.1, 1.4, Nothing... From other side it
>> seems to be logical. Why not.
>> Thanks for the idea :)
>>
>> On Tue, Sep 15, 2009 at 12:05 PM, Lyndon Maydwell 
>> wrote:
>>>
>>> I think the problem is that you want to compose a list with no
>>> indication of weather one member can have a perimeter or not. I'm not
>>> sure if this is a good solution or not, but I immediately think to
>>> make all Geometry objects instances of a class that return a Maybe
>>> value for the perimeter:
>>>
>>> e.g.
>>>
>>> ---
>>>
>>> import Data.Maybe
>>>
>>> data Geometry = Sphere Position Radius | Circle Position Radius deriving
>>> (Show)
>>>
>>> type Position = (Double, Double)
>>> type Radius = Double
>>> type Height = Double
>>>
>>> class Encircled x where
>>>        perimeter :: x -> Maybe Double
>>>
>>> instance Encircled Geometry where
>>>        perimeter (Sphere _ r) = Nothing
>>>        perimeter (Circle _ r) = Just $ 2.0 * pi * r
>>>
>>> list = [Sphere (1,1) 1, Circle (2,2) 2]
>>>
>>> main = (print . catMaybes . map perimeter) list
>>>
>>> --- [12.566370614359172]
>>>
>>> On Tue, Sep 15, 2009 at 6:29 PM, Olex P  wrote:
>>> > Hey guys,
>>> >
>>> > It's a dumb question but I'd like to know a right answer...
>>> > Let's say we have some geometry data that can be Sphere, Cylinder,
>>> > Circle
>>> > and so on. We can implement it as new data type plus a bunch of
>>> > functions
>>> > that work on this data:
>>> >
>>> > data Geometry = Sphere Position Radius
>>> >                         | Cylinder Position Radius Height
>>> >                         | Circle Position Radius
>>> >     deriving (Show)
>>> >
>>> > perimeter (Sphere _ r) = 0.0
>>> > perimeter (Cylinder _ r h) = 0.0
>>> > perimeter (Circle _ r) = 2.0 * pi * r
>>> >
>>> > Perimeter doesn't make sense for Sphere or Cylinder. So we could define
>>> > a
>>> > type class for objects that have perimeter and make an instance of it
>>> > only
>>> > for Circle (data Circle = Circle Position Radius). Make sense. But
>>> > these
>>> > three functions above have desired behaviour. If user has a list of
>>> > objects
>>> > like [Sphere, Circle, Circle, Cylinder] he would like to calculate
>>> > perimeters of each object using map perimerer list (in this case we
>>> > also
>>> > have to modify Geometry data type).
>>> > So we could make instances of "perimeter" type class for all objects
>>> > and
>>> > return zero in case if perimeter doesn't make sense.
>>> > Same as previous version but with typeclasses and with additional
>>> > constructors (constructors for each type of object + constructors in
>>> > Geometry data). Looks a bit overcomplicated.
>>> > Any reasons to use type classes in this case? Maybe there is something
>>> > I'm
>>> > missing?
>>> >
>>> > Cheers,
>>> > -O
>>> >
>>> > ___
>>> > 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] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
Well... How this:

instance Encircled Geometry where
   perimeter (Sphere _ r) = Nothing
   perimeter (Circle _ r) = Just $ 2.0 * pi * r

differs from this:

perimeter :: Geometry -> Maybe Double
perimeter (Sphere _ r) = Nothing
perimeter (Circle _ r) = Just $ 2.0 * pi * r

and from this:

perimeter :: Geometry -> Double
perimeter (Sphere _ r) = 0.0
perimeter (Circle _ r) = 2.0 * pi * r

The latter is even simpler because there is no need in extraction of Double
value from Maybe.
So the question is still there: do I need a type class?

On Tue, Sep 15, 2009 at 12:21 PM, Olex P  wrote:

> Sure! I completely forgot about Maybe. The only one question is is it good
> from the point of view of ordinary user who doesn't know about such things
> like functional programming, monads etc. Imagine average user who is looking
> into a spreadsheet and sees values 0.1, 1.4, Nothing... From other side it
> seems to be logical. Why not.
> Thanks for the idea :)
>
> On Tue, Sep 15, 2009 at 12:05 PM, Lyndon Maydwell wrote:
>
>> I think the problem is that you want to compose a list with no
>> indication of weather one member can have a perimeter or not. I'm not
>> sure if this is a good solution or not, but I immediately think to
>> make all Geometry objects instances of a class that return a Maybe
>> value for the perimeter:
>>
>> e.g.
>>
>> ---
>>
>> import Data.Maybe
>>
>> data Geometry = Sphere Position Radius | Circle Position Radius deriving
>> (Show)
>>
>> type Position = (Double, Double)
>> type Radius = Double
>> type Height = Double
>>
>> class Encircled x where
>>perimeter :: x -> Maybe Double
>>
>> instance Encircled Geometry where
>>perimeter (Sphere _ r) = Nothing
>>perimeter (Circle _ r) = Just $ 2.0 * pi * r
>>
>> list = [Sphere (1,1) 1, Circle (2,2) 2]
>>
>> main = (print . catMaybes . map perimeter) list
>>
>> --- [12.566370614359172]
>>
>> On Tue, Sep 15, 2009 at 6:29 PM, Olex P  wrote:
>> > Hey guys,
>> >
>> > It's a dumb question but I'd like to know a right answer...
>> > Let's say we have some geometry data that can be Sphere, Cylinder,
>> Circle
>> > and so on. We can implement it as new data type plus a bunch of
>> functions
>> > that work on this data:
>> >
>> > data Geometry = Sphere Position Radius
>> > | Cylinder Position Radius Height
>> > | Circle Position Radius
>> > deriving (Show)
>> >
>> > perimeter (Sphere _ r) = 0.0
>> > perimeter (Cylinder _ r h) = 0.0
>> > perimeter (Circle _ r) = 2.0 * pi * r
>> >
>> > Perimeter doesn't make sense for Sphere or Cylinder. So we could define
>> a
>> > type class for objects that have perimeter and make an instance of it
>> only
>> > for Circle (data Circle = Circle Position Radius). Make sense. But these
>> > three functions above have desired behaviour. If user has a list of
>> objects
>> > like [Sphere, Circle, Circle, Cylinder] he would like to calculate
>> > perimeters of each object using map perimerer list (in this case we also
>> > have to modify Geometry data type).
>> > So we could make instances of "perimeter" type class for all objects and
>> > return zero in case if perimeter doesn't make sense.
>> > Same as previous version but with typeclasses and with additional
>> > constructors (constructors for each type of object + constructors in
>> > Geometry data). Looks a bit overcomplicated.
>> > Any reasons to use type classes in this case? Maybe there is something
>> I'm
>> > missing?
>> >
>> > Cheers,
>> > -O
>> >
>> > ___
>> > 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] ANNOUNCE: LambdaINet-0.1.0, Graphical Interaction Net Evaluator for Optimal Evaluation

2009-09-15 Thread Paul L
Now it's at version 0.1.2 with the EnableGUI fix for Mac OS X.

On 9/14/09, Paul L  wrote:
> I just bumped the version to 0.1.1 that fixes an embarrassing bug,
> i.e., the first example shown on the screen was actually wrong.
>
> I took a screenshot of the interaction net showing (church 2) f x,
> i.e., (\f x -> f (f x)) f x together with on-screen help messages. It
> is the first example right after you start the LambdaINet application,
> and erase redundant nodes, relayout, and auto zoom (key sequence E, L,
> Space"). It will reduce to f (f x) if you hit R key, or if you want to
> see the step by step outermost reduction, just keep hitting O key.
>
> The picture is here
> http://www.thev.net/download/church_2_f_x-with-helpmsg.jpg
>
> Pressing 1 to 9 will show a more complicated example that actually
> demonstrates the power of optimal evaluation:  opt n = (church n)
> (church 2) i i. Standard call-by-need takes 37 beta reductions to
> evaluate opt 4, but optimal only needs 15.
>
> On 9/14/09, Bas van Dijk  wrote:
>> On Mon, Sep 14, 2009 at 7:36 AM, Paul L  wrote:
>>> It's available on Hackage DB at
>>> http://hackage.haskell.org/package/LambdaINet
>>
>> Nice! Screenshots anywhere?
>>
>> Bas
>>
>
>
> --
> Regards,
> Paul Liu
>
> Yale Haskell Group
> http://www.haskell.org/yale
>


-- 
Regards,
Paul Liu

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


Re: [Haskell-cafe] HDBC Oracle bindings(?/!)

2009-09-15 Thread Daniil Elovkov


Hello Thiago, John.

I've taken the Oracle HDBC driver at
http://thiagoarrais.com/repos/hdbc-oracle

modified it just a little to suite 6.10.4 and briefly looked if it works.

It does, that's cool! Thanks Thiago!

A question follows, maybe it's worth to mention it at the HDBC page 
and/or put it to Hackage?


And another question: Thiago, John how do you think what is the 
appropriate place to put the function that sets prefetch row count?


The thing is that (at least in my case) by default Oracle returns rows 
very slowly. Setting prefetch count speeds it up dramatically.


It's not the case with MySQL, for example, but the functionality is 
never the less quite generic. For example, this method is part of JDBC api.




Thiago Arrais wrote:

John,

On Thu, Oct 30, 2008 at 2:48 PM, John Goerzen  wrote:

I would certainly happily reference anyone's native Oracle HDBC
backend too, though!


You may want to reference mine, given that there aren't any others
currently. Just be aware that it really isn't ready for mass
consumption yet.



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


Re: Re[2]: [Haskell-cafe] Cabal install on Windows 7

2009-09-15 Thread Peter Verswyvelen
Yes, I'm aware of that, but not the details, so thanks for the info.

Anyway, I quickly tested Regis's idea in C#, and it works as he said.

http://hpaste.org/fastcgi/hpaste.fcgi/view?id=9392#a9392
- When trying to create a folder in ProgramFiles, you get an access
denied exception, unless the program is run as admin.
- When trying to "shellexec" a program requiring admin rights - in
this case regedit.exe - you get a popup, unless run as admin

So this looks like a really clever & simple solution :-)

On Tue, Sep 15, 2009 at 11:49 AM, Bulat Ziganshin
 wrote:
> Hello Peter,
>
> Tuesday, September 15, 2009, 1:24:26 PM, you wrote:
>
> in order to protect from viruses and so now windows programs should be
> split into two parts - one that doesn't need admin privileges and one
> that needs them. as far as your actions doesn't need second part, you
> are running first program, when things haapened that needs admin
> priv., second executable should be run and *OS* will ask whether yot
> trust it. so it's pretty the same as sudo built-in in the system via
> exe manifest files. with UAC enabled, you are never have admin
> privileges while you run only first part of program
>
>> It is possible for an executable with less privileges to
>> "shellexecute" an executable that requires admin rights? Won't this
>> immediately raise an "access denied" or other security exception
>> again? Don't know, it might be possible, but it's worth to check it
>> out before going this route (which is rather clever IMHO :)
>
>> On Tue, Sep 15, 2009 at 10:14 AM, Regis Saint-Paul
>>  wrote:
>>>
 > - use windows API for requesting elevation during the process (ugly)

 If it really has to be done, then this seems like the best approach. In
 principle there's no problem with calling funky win32 functions in
 Cabal, it's mostly a matter of working out what bahaviour we want and
 what UAC lets us do.
>>>
>>> To achieve this, a candidate solution would be:
>>> - to have a separate executable with a manifest indicating that
>>> administrator privilege are needed (and, ideally, signed) and able to
>>> perform the tasks necessitating elevation
>>> - from cabal, to run this separate process (calling shellexecute) exactly at
>>> the point when elevation is needed
>>> - alternatively, it might be possible to try the operation, catch the
>>> exception that would happen if it fails, and call the separate process in
>>> this case (see:
>>> http://stackoverflow.com/questions/17533/request-vista-uac-elevation-if-path
>>> -is-protected#17544)
>>>
>>> The advantage is that, with this solution, users only use "cabal" and the
>>> elevation is performed when needed.
>>>
>>> By contrast, the other suggested solution of having two executables
>>> (cabal-user and cabal-global) leaves the choice of elevating cabal to the
>>> user and only needs to modify the build process (no code changed in cabal).
>>> Its drawback is that elevation will be requested even when unnecessary every
>>> time cabal-global is launched.
>>>
>>> So a first task would be to identify the cases where cabal needs to run with
>>> elevated rights and the task to perform in that case.
>>> - Is cabal going to be modified to use AppData for library install?
>>> - If this is the case, then writing in protected folders would be only for
>>> binary install (with cabal install). Are there other cases?
>>> - If this is not the case, then writing in protected folder is for all
>>> package install when in global mode...other cases?
>>> - Am I missing operations where cabal would need admin privileges? For
>>> instance, may cabal need to modify some environment variable?
>>>
>>> Cheers,
>>> Regis
>>>
>>> ___
>>> 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
>
>
> --
> Best regards,
>  Bulat                            mailto:bulat.zigans...@gmail.com
>
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parallel graphics

2009-09-15 Thread minh thu
Hi Andrew,

2009/9/15 Andrew Coppin :
> ...
> I'm presuming that sparking every individual point is going to create
> billions of absolutely tiny sparks, which probably won't give great
> performance. We could spark every line rather than every point?
> ...

You should just try: no one can say if pixels, lines, image buckets or
complete images is the right granularity.
As for progress information, probably the needed granularity is not
the same as the above one.

Also, parallelizing a raytracer or the computation of a simple
function of coordinates won't need the same solution. For instance ray
coherence can be used to more efficiently traverse the accelarating
data structure of the raytracer with many rays at once.

Maybe before looking at what haskell has to offer you should look how
your program can be parallelized then see if your solution maps well
to one of haskell technical solutions.

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


[Haskell-cafe] Parallel graphics

2009-09-15 Thread Andrew Coppin
I have a number of compute-bound graphics programs written in Haskell. 
(Fractal generators, ray tracers, that kind of thing.) GHC offers 
several concurrency and parallelism abstractions, but what's the best 
way to use these to get images rendered as fast as possible, using the 
available compute power?


(OK, well the *best* way is to use the GPU. But AFAIK that's still a 
theoretical research project, so we'll leave that for now.)


I've identified a couple of common cases. You have a 2D grid of points, 
and you want to compute the value at each point. Eventually you will 
have a grid of /pixels/ where each value is a /colour/, but there may be 
intermediate steps before that. So, what cases exist?


1. A point's value is a function of its coordinates.

2. A point's value is a function of its previous value from the last frame.

3. A point's value is a function of /several/ points from the last frame.

How can we accelerate this? I see a few options:

- Create a spark for every point in the grid.
- Create several explicit threads to populate non-overlapping regions of 
the grid.

- Use parallel arrays. (Does this actually works yet??)

I'm presuming that sparking every individual point is going to create 
billions of absolutely tiny sparks, which probably won't give great 
performance. We could spark every line rather than every point?


Using explicit threads has the nice side-effect that we can produce 
progress information. Few things are more frustrating than staring at a 
blank screen with no idea how long it's going to take. I'm thinking this 
method might also allow you to avoid two cores tripping over each 
other's caches.


And then there's parallel arrays, which presumably are designed from the 
ground up for exactly this type of task. But are they usable yet?


Any further options?

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


Re: [Haskell-cafe] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
Sure! I completely forgot about Maybe. The only one question is is it good
from the point of view of ordinary user who doesn't know about such things
like functional programming, monads etc. Imagine average user who is looking
into a spreadsheet and sees values 0.1, 1.4, Nothing... From other side it
seems to be logical. Why not.
Thanks for the idea :)

On Tue, Sep 15, 2009 at 12:05 PM, Lyndon Maydwell wrote:

> I think the problem is that you want to compose a list with no
> indication of weather one member can have a perimeter or not. I'm not
> sure if this is a good solution or not, but I immediately think to
> make all Geometry objects instances of a class that return a Maybe
> value for the perimeter:
>
> e.g.
>
> ---
>
> import Data.Maybe
>
> data Geometry = Sphere Position Radius | Circle Position Radius deriving
> (Show)
>
> type Position = (Double, Double)
> type Radius = Double
> type Height = Double
>
> class Encircled x where
>perimeter :: x -> Maybe Double
>
> instance Encircled Geometry where
>perimeter (Sphere _ r) = Nothing
>perimeter (Circle _ r) = Just $ 2.0 * pi * r
>
> list = [Sphere (1,1) 1, Circle (2,2) 2]
>
> main = (print . catMaybes . map perimeter) list
>
> --- [12.566370614359172]
>
> On Tue, Sep 15, 2009 at 6:29 PM, Olex P  wrote:
> > Hey guys,
> >
> > It's a dumb question but I'd like to know a right answer...
> > Let's say we have some geometry data that can be Sphere, Cylinder, Circle
> > and so on. We can implement it as new data type plus a bunch of functions
> > that work on this data:
> >
> > data Geometry = Sphere Position Radius
> > | Cylinder Position Radius Height
> > | Circle Position Radius
> > deriving (Show)
> >
> > perimeter (Sphere _ r) = 0.0
> > perimeter (Cylinder _ r h) = 0.0
> > perimeter (Circle _ r) = 2.0 * pi * r
> >
> > Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
> > type class for objects that have perimeter and make an instance of it
> only
> > for Circle (data Circle = Circle Position Radius). Make sense. But these
> > three functions above have desired behaviour. If user has a list of
> objects
> > like [Sphere, Circle, Circle, Cylinder] he would like to calculate
> > perimeters of each object using map perimerer list (in this case we also
> > have to modify Geometry data type).
> > So we could make instances of "perimeter" type class for all objects and
> > return zero in case if perimeter doesn't make sense.
> > Same as previous version but with typeclasses and with additional
> > constructors (constructors for each type of object + constructors in
> > Geometry data). Looks a bit overcomplicated.
> > Any reasons to use type classes in this case? Maybe there is something
> I'm
> > missing?
> >
> > Cheers,
> > -O
> >
> > ___
> > 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] Typeclasses vs simple functions?

2009-09-15 Thread Olex P
Hey guys,

It's a dumb question but I'd like to know a right answer...
Let's say we have some geometry data that can be Sphere, Cylinder, Circle
and so on. We can implement it as new data type plus a bunch of functions
that work on this data:

data Geometry = Sphere Position Radius
| Cylinder Position Radius Height
| Circle Position Radius
deriving (Show)

perimeter (Sphere _ r) = 0.0
perimeter (Cylinder _ r h) = 0.0
perimeter (Circle _ r) = 2.0 * pi * r

Perimeter doesn't make sense for Sphere or Cylinder. So we could define a
type class for objects that have perimeter and make an instance of it only
for Circle (data Circle = Circle Position Radius). Make sense. But these
three functions above have desired behaviour. If user has a list of objects
like [Sphere, Circle, Circle, Cylinder] he would like to calculate
perimeters of each object using map perimerer list (in this case we also
have to modify Geometry data type).
So we could make instances of "perimeter" type class for all objects and
return zero in case if perimeter doesn't make sense.
Same as previous version but with typeclasses and with additional
constructors (constructors for each type of object + constructors in
Geometry data). Looks a bit overcomplicated.
Any reasons to use type classes in this case? Maybe there is something I'm
missing?

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


Re[2]: [Haskell-cafe] Cabal install on Windows 7

2009-09-15 Thread Bulat Ziganshin
Hello Peter,

Tuesday, September 15, 2009, 1:24:26 PM, you wrote:

in order to protect from viruses and so now windows programs should be
split into two parts - one that doesn't need admin privileges and one
that needs them. as far as your actions doesn't need second part, you
are running first program, when things haapened that needs admin
priv., second executable should be run and *OS* will ask whether yot
trust it. so it's pretty the same as sudo built-in in the system via
exe manifest files. with UAC enabled, you are never have admin
privileges while you run only first part of program

> It is possible for an executable with less privileges to
> "shellexecute" an executable that requires admin rights? Won't this
> immediately raise an "access denied" or other security exception
> again? Don't know, it might be possible, but it's worth to check it
> out before going this route (which is rather clever IMHO :)

> On Tue, Sep 15, 2009 at 10:14 AM, Regis Saint-Paul
>  wrote:
>>
>>> > - use windows API for requesting elevation during the process (ugly)
>>>
>>> If it really has to be done, then this seems like the best approach. In
>>> principle there's no problem with calling funky win32 functions in
>>> Cabal, it's mostly a matter of working out what bahaviour we want and
>>> what UAC lets us do.
>>
>> To achieve this, a candidate solution would be:
>> - to have a separate executable with a manifest indicating that
>> administrator privilege are needed (and, ideally, signed) and able to
>> perform the tasks necessitating elevation
>> - from cabal, to run this separate process (calling shellexecute) exactly at
>> the point when elevation is needed
>> - alternatively, it might be possible to try the operation, catch the
>> exception that would happen if it fails, and call the separate process in
>> this case (see:
>> http://stackoverflow.com/questions/17533/request-vista-uac-elevation-if-path
>> -is-protected#17544)
>>
>> The advantage is that, with this solution, users only use "cabal" and the
>> elevation is performed when needed.
>>
>> By contrast, the other suggested solution of having two executables
>> (cabal-user and cabal-global) leaves the choice of elevating cabal to the
>> user and only needs to modify the build process (no code changed in cabal).
>> Its drawback is that elevation will be requested even when unnecessary every
>> time cabal-global is launched.
>>
>> So a first task would be to identify the cases where cabal needs to run with
>> elevated rights and the task to perform in that case.
>> - Is cabal going to be modified to use AppData for library install?
>> - If this is the case, then writing in protected folders would be only for
>> binary install (with cabal install). Are there other cases?
>> - If this is not the case, then writing in protected folder is for all
>> package install when in global mode...other cases?
>> - Am I missing operations where cabal would need admin privileges? For
>> instance, may cabal need to modify some environment variable?
>>
>> Cheers,
>> Regis
>>
>> ___
>> 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


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

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


Re: [Haskell-cafe] Cabal install on Windows 7

2009-09-15 Thread Peter Verswyvelen
It is possible for an executable with less privileges to
"shellexecute" an executable that requires admin rights? Won't this
immediately raise an "access denied" or other security exception
again? Don't know, it might be possible, but it's worth to check it
out before going this route (which is rather clever IMHO :)

On Tue, Sep 15, 2009 at 10:14 AM, Regis Saint-Paul
 wrote:
>
>> > - use windows API for requesting elevation during the process (ugly)
>>
>> If it really has to be done, then this seems like the best approach. In
>> principle there's no problem with calling funky win32 functions in
>> Cabal, it's mostly a matter of working out what bahaviour we want and
>> what UAC lets us do.
>
> To achieve this, a candidate solution would be:
> - to have a separate executable with a manifest indicating that
> administrator privilege are needed (and, ideally, signed) and able to
> perform the tasks necessitating elevation
> - from cabal, to run this separate process (calling shellexecute) exactly at
> the point when elevation is needed
> - alternatively, it might be possible to try the operation, catch the
> exception that would happen if it fails, and call the separate process in
> this case (see:
> http://stackoverflow.com/questions/17533/request-vista-uac-elevation-if-path
> -is-protected#17544)
>
> The advantage is that, with this solution, users only use "cabal" and the
> elevation is performed when needed.
>
> By contrast, the other suggested solution of having two executables
> (cabal-user and cabal-global) leaves the choice of elevating cabal to the
> user and only needs to modify the build process (no code changed in cabal).
> Its drawback is that elevation will be requested even when unnecessary every
> time cabal-global is launched.
>
> So a first task would be to identify the cases where cabal needs to run with
> elevated rights and the task to perform in that case.
> - Is cabal going to be modified to use AppData for library install?
> - If this is the case, then writing in protected folders would be only for
> binary install (with cabal install). Are there other cases?
> - If this is not the case, then writing in protected folder is for all
> package install when in global mode...other cases?
> - Am I missing operations where cabal would need admin privileges? For
> instance, may cabal need to modify some environment variable?
>
> Cheers,
> Regis
>
> ___
> 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] Cabal install on Windows 7

2009-09-15 Thread Regis Saint-Paul

> > - use windows API for requesting elevation during the process (ugly)
> 
> If it really has to be done, then this seems like the best approach. In
> principle there's no problem with calling funky win32 functions in
> Cabal, it's mostly a matter of working out what bahaviour we want and
> what UAC lets us do.

To achieve this, a candidate solution would be: 
- to have a separate executable with a manifest indicating that
administrator privilege are needed (and, ideally, signed) and able to
perform the tasks necessitating elevation
- from cabal, to run this separate process (calling shellexecute) exactly at
the point when elevation is needed 
- alternatively, it might be possible to try the operation, catch the
exception that would happen if it fails, and call the separate process in
this case (see:
http://stackoverflow.com/questions/17533/request-vista-uac-elevation-if-path
-is-protected#17544)

The advantage is that, with this solution, users only use "cabal" and the
elevation is performed when needed.
 
By contrast, the other suggested solution of having two executables
(cabal-user and cabal-global) leaves the choice of elevating cabal to the
user and only needs to modify the build process (no code changed in cabal).
Its drawback is that elevation will be requested even when unnecessary every
time cabal-global is launched. 

So a first task would be to identify the cases where cabal needs to run with
elevated rights and the task to perform in that case. 
- Is cabal going to be modified to use AppData for library install? 
- If this is the case, then writing in protected folders would be only for
binary install (with cabal install). Are there other cases?
- If this is not the case, then writing in protected folder is for all
package install when in global mode...other cases? 
- Am I missing operations where cabal would need admin privileges? For
instance, may cabal need to modify some environment variable? 

Cheers,
Regis

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