Re: [Haskell-cafe] REALLY simple STRef examples

2006-07-21 Thread Bryan Burgers

On 7/21/06, S C Kuo <[EMAIL PROTECTED]> wrote:

Not totally relevant to what the discussion has evolved to, but I wrote
a factorial function using STRefs (in the spirit of the Evolution of a
Haskell programmer) and I think it qualifies as a really simple example.
Code follows:

import Data.STRef
import Control.Monad.ST

foreach :: (Monad m) => [a] -> (a -> m b) -> m ()
foreach = flip mapM_
-- Bryn Keller's foreach, but with type restrictions

fac :: (Num a, Enum a) => a -> a
fac n   = runST (fac' n)

fac':: (Num a, Enum a) => a -> ST s a
fac' n  = dor <- newSTRef 1
foreach [1..n] (\x -> modifySTRef r (*x))
x <- readSTRef r
return x


Forgive me for not understanding, but I was hoping you would explain a
choice you made in your code. Why did you define foreach and then use


foreach [1..n] (\x -> modifySTRef r (*x))


Instead of simply using


mapM_ (\x -> modifySTRef r (*x)) [1..n]


? I tried it out in GHCi, and it worked fine, and I have seen code
that has been defined as a flip to take advantage of partial
application. But your code doesn't seem to take advantage of partial
application, so why did you define 'foreach' and then use it instead
of using 'mapM_'? I am just curious, and have always been interested
in reasons behind coding style.

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


[Haskell-cafe] incoherent instance selection when it should be still coherent

2006-07-21 Thread Ralf Lammel
The following pain is sort of ghc (6.4.2) specific.
(The same behavior is achievable with hugs -98 +O which is Ok in so far
that +O (as opposed to +o) is not strongly supposed to be coherent.)

Note the following GHC options preceding the code.
They do not contain -fallow-incoherent-instances.

{-# OPTIONS -fglasgow-exts #-}

{-# OPTIONS -fallow-undecidable-instances #-}

{-# OPTIONS -fallow-overlapping-instances #-}


-- A single parameter class with two silly instances

class Foo x where foo :: x -> (); foo = const ()

instance Foo ()

instance Foo Bool


-- A two-parameter class with a generic and a non-generic instance

class (Foo x, Foo y) => Bar x y where bar :: x -> y -> String

instance (Foo x, Foo y) => Bar x y where bar _ _ = "generic instance"

instance Foo z => Bar () z where bar _ _ = "non-generic instance"


-- An existential wrapper around foos

data Wrap = forall x. Foo x => Wrap x


-- A wrapper-based variation on the type-class member bar

uuh :: Wrap -> Wrap -> String

uuh (Wrap x) (Wrap y) = bar x y


-- Let's try all unwrapped and wrapped combinations of bar and uuh

t1 = ()

t2 = True

w1 = Wrap t1

w2 = Wrap t2

main = do 
  print $ bar t1 t1
  print $ uuh w1 w1 -- uuh!
  print $ bar t1 t2
  print $ uuh w1 w2 -- uuh!
  print $ bar t2 t1
  print $ uuh w2 w1
  print $ bar t2 t2
  print $ uuh w2 w2

We get:

{-

"non-generic instance"
"generic instance"
"non-generic instance"
"generic instance"
"generic instance"
"generic instance"
"generic instance"
"generic instance"

-}

This means that the generic instance is consistently chosen by uuh.
This is clearly incoherent.
I would also complain that uuh type-checks in the first place.
Opinions?

Regards,
Ralf

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


Re: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-21 Thread David Menendez
Neil Mitchell writes:

> >  We should avoid referring to $PATH as the "path", since we
> > already have FilePath.
> Agreed, but I couldn't come up with a better name, if anyone has any
> suggestions.

searchPath?
-- 
David Menendez <[EMAIL PROTECTED]> 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] REALLY simple STRef examples

2006-07-21 Thread S C Kuo
Not totally relevant to what the discussion has evolved to, but I wrote 
a factorial function using STRefs (in the spirit of the Evolution of a 
Haskell programmer) and I think it qualifies as a really simple example. 
Code follows:


import Data.STRef
import Control.Monad.ST

foreach :: (Monad m) => [a] -> (a -> m b) -> m ()
foreach = flip mapM_
-- Bryn Keller's foreach, but with type restrictions

fac :: (Num a, Enum a) => a -> a
fac n   = runST (fac' n)

fac':: (Num a, Enum a) => a -> ST s a
fac' n  = dor <- newSTRef 1
foreach [1..n] (\x -> modifySTRef r (*x))
x <- readSTRef r
return x

Chad Scherrer wrote:

The IO monad hasn't given me too much trouble, but I want to be sure
to structure things the way "they should be". If I get everything
running using IO first and then have type-checking problems with ST,
it will be tempting to just slap on an unsafePerformIO and call it
good. Sure, it's really doing the same thing anyway, but it just comes
out looking like a hack.

On 7/20/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:

Hello Chad,

Friday, July 21, 2006, 12:26:58 AM, you wrote:

> Ok, I see now why the return is necessary.

btw, it may be helpful to read "IO inside" material. ST monad is not
very different from IO monad - it only limited to operations on STRef
and STArray, so that it can't have side-effects visible outside of
runST statement used to run ST computation


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


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


[Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-21 Thread Neil Mitchell

Hi,


I haven't been following this discussion very closely, but this caught my eye.
Has anyone pointed out yet that eliminating ".." in a FilePath isn't valid in
the presence of symbolic links?  I vaguely recall that this is why Krasimir's
System.FilePath library doesn't include normalisation.  Normalisation that just
changes separators, removes redundant separators and removes "." components is
probably ok.

Ok, I'll remove this behaviour


I don't really see the point of fullPathWith.  Isn't it just combine?

It also applies normalise to the result, although I'm not sure thats a
particularly useful thing to do. I'll think about this.


I think shortPath is on dodgy ground, given the difficulty with normalising
FilePaths, and the fact that paths are not unique in the presence of symlinks.

I think this is still a useful thing, but I'll think harder about it
in relation to symlinks, and figure out what properties it should
have.


The temporary file stuff is wrong - see System.IO.openTemporaryFile.  The only
way to reliably create a temporary file is to open it at the same time,
otherwise there's a race condition.

Looking at it again, I'm not sure that the temporary operations belong
in this module. Ditto for the directory operations. It would be handy
if the directory operations (particularly ensureDirectory) were
somewhere else in the standard libraries though.


I have some other issues with naming, and the fact that the library mixes IO and
non-IO functions.

I think this is unavoidable, I tried to make as many functions as
possible pure, but where the filesystem must be consulted they have to
be IO based. For example canonicalPath probably belongs in this
module, but has to be IO based.


 We should avoid referring to $PATH as the "path", since we
already have FilePath.

Agreed, but I couldn't come up with a better name, if anyone has any
suggestions.


Where you use the term Filename, I think it should probably
be FilePath. I think we should consistently use a single term, preferably 
FilePath.

I have tried to consistently use FilePath as a path to a file, and
filename as the actual name once you get there. For example:

/usr/bin/ghc

Has a FilePath of "/usr/bin/ghc" and a FileName of "ghc". That
distinction seems more logical to me, but if everyone thinks otherwise
I'm happy to change it.

Thanks

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


[Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-21 Thread Simon Marlow

Neil Mitchell wrote:


I have also added a canonicalPath function, support for spotting
file\con as invalid and fixing it, support for \\?\ paths (if you
don't know what they are, don't look it up, they are quite painful!)
and a few very obscure corner cases which broke some of the
properties.


I haven't been following this discussion very closely, but this caught my eye. 
Has anyone pointed out yet that eliminating ".." in a FilePath isn't valid in 
the presence of symbolic links?  I vaguely recall that this is why Krasimir's 
System.FilePath library doesn't include normalisation.  Normalisation that just 
changes separators, removes redundant separators and removes "." components is 
probably ok.


I don't really see the point of fullPathWith.  Isn't it just combine?

I think shortPath is on dodgy ground, given the difficulty with normalising 
FilePaths, and the fact that paths are not unique in the presence of symlinks.


The temporary file stuff is wrong - see System.IO.openTemporaryFile.  The only 
way to reliably create a temporary file is to open it at the same time, 
otherwise there's a race condition.


I have some other issues with naming, and the fact that the library mixes IO and 
non-IO functions.  We should avoid referring to $PATH as the "path", since we 
already have FilePath.  eg. spiltPath and getPath are talking about two very 
different things.  Where you use the term Filename, I think it should probably 
be FilePath.  I think we should consistently use a single term, preferably FilePath.


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


Re: Re[4]: [Haskell-cafe] REALLY simple STRef examples

2006-07-21 Thread Chad Scherrer

The IO monad hasn't given me too much trouble, but I want to be sure
to structure things the way "they should be". If I get everything
running using IO first and then have type-checking problems with ST,
it will be tempting to just slap on an unsafePerformIO and call it
good. Sure, it's really doing the same thing anyway, but it just comes
out looking like a hack.

On 7/20/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:

Hello Chad,

Friday, July 21, 2006, 12:26:58 AM, you wrote:

> Ok, I see now why the return is necessary.

btw, it may be helpful to read "IO inside" material. ST monad is not
very different from IO monad - it only limited to operations on STRef
and STArray, so that it can't have side-effects visible outside of
runST statement used to run ST computation


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


[Haskell-cafe] HXT - problems with runIOSLA or xread

2006-07-21 Thread Niklas

Hi everybody,

and especially Uwe Schmidt et al.

I ran into some problems trying to process some xml from a string source,
illustrated in the code below. From file, using readDocument, everything works
great though. I've probably missed a finer detail or two in the arrow handling,
or it could be a bug in HXT (if I run the code in ghci, it will crash hard).

Output:
-->main.exe
NTree (XTag (QN {namePrefix = "", localPart = "small", namespaceUri = ""}) []) [
NTree (XTag (QN {namePrefix = "", localPart = "xml", namespaceUri = ""}) []) [],
NTree (XTag (QN {namePrefix = "", localPart = "example", namespaceUri = ""}) [])
 []]
-->

So it seems that the string gets read, since it shows up as a result from
procString, but I get no output from writeDocument in writeStrDoc. Could anybody
enlighten me?

I'm using GHC 6.5 and HXT 6.0 on Windows XP.

Regards,

/Niklas

---8<---

module Main where

import Text.XML.HXT.Arrow

wa = [(a_indent, "1"), (a_remove_whitespace, "1")]

main = procString tststr >>= mapM_ print . snd

procString = runIOSLA writeStrDoc (initialState ())

writeStrDoc = xread >>> writeDocument wa "-"

tststr = ""

--->8---


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


[Haskell-cafe] Still not dead

2006-07-21 Thread Einar Karttunen
Hello

As many of you may have noticed I have been away for some months.
This has been due to health problems which have unfortunately
kept me unable to work on Haskell projects.

I am not dead and will be working on resolving the backlog
of messages (will probably take a week). I will be slowly
back to hacking things when I get everything fixed.

- Einar Karttunen

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


Re: [Haskell-cafe] seq - RTFM?

2006-07-21 Thread Christophe Poucet
Hello Dusan,

The reason why that does not work as you expect it to is because the
type of the whole expression is not monadic.  Therefore it will
basically evaluate the action until it's an action ready to be executed,
but not execute it, cause it's not in the IO monad.  It's the same as
having a list of [putStr "a", putStr "b"].  Until you start placing
these actions in the IO monad, they'll just be values.

Hope that's somewhat clear

Dusan Kolar wrote:
> Hello all,
> 
>  my question is probably dull. So answers to better investigate manual
> are welcome. Why is this correct?
> 
>   ___ ___ _
>  / _ \ /\  /\/ __(_)
> / /_\// /_/ / /  | |  GHC Interactive, version 6.4.1, for Haskell 98.
> / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
> \/\/ /_/\/|_|  Type :? for help.
> 
> Loading package base-1.0 ... linking ... done.
> Prelude> putStr "Ahoj\n"
> Ahoj
> Prelude> putStr "Ahoj\n" `seq` 3+3
> 6
> Prelude> :q
> Leaving GHCi.
> 
> And not
> 
> Prelude> putStr "Ahoj\n"
> Ahoj
> Prelude> putStr "Ahoj\n" `seq` 3+3
> Ahoj
> 6
> 
> ???
> 
> Does it have something common with monads or is it a behavior of seq?
> 
> Thanks,
> 
>  Dusan
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 


-- 
Christophe Poucet
Ph.D. Student
DESICS - DDT

Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
IMEC vzw -- Register of Legal Entities Leuven VAT BE 0425.260.668 --
Kapeldreef 75, B-3001 Leuven, Belgium -- http://www.imec.be

http://www.imec.be/wwwinter/email-disclaimer.shtml>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seq - RTFM?

2006-07-21 Thread Jens Fisseler
Hi Dusan,

>   my question is probably dull. So answers to better investigate manual 
> are welcome. Why is this correct?

the Haskell Report is probably better in explaining the behaviour of
'seq' than me: 
http://haskell.org/onlinereport/basic.html#sect6.2

Regards,

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


Re: [Haskell-cafe] seq - RTFM?

2006-07-21 Thread Piotr Kalinowski

On 21/07/06, Dusan Kolar <[EMAIL PROTECTED]> wrote:

Prelude> putStr "Ahoj\n"
Ahoj
Prelude> putStr "Ahoj\n" `seq` 3+3
6
Prelude> :q
Leaving GHCi.

And not

Prelude> putStr "Ahoj\n"
Ahoj
Prelude> putStr "Ahoj\n" `seq` 3+3
Ahoj
6


Well, I understand that seq evaluates the first argument. But the
result of evaluating putStr is a monadic action. Not execution of that
action.

Regards,
Piotr Kalinowski


--
Intelligence is like a river: the deeper it is, the less noise it makes
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] seq - RTFM?

2006-07-21 Thread Dusan Kolar

Hello all,

 my question is probably dull. So answers to better investigate manual 
are welcome. Why is this correct?


  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.4.1, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base-1.0 ... linking ... done.
Prelude> putStr "Ahoj\n"
Ahoj
Prelude> putStr "Ahoj\n" `seq` 3+3
6
Prelude> :q
Leaving GHCi.

And not

Prelude> putStr "Ahoj\n"
Ahoj
Prelude> putStr "Ahoj\n" `seq` 3+3
Ahoj
6

???

Does it have something common with monads or is it a behavior of seq?

Thanks,

 Dusan


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


RE: Re[4]: [Haskell-cafe] REALLY simple STRef examples

2006-07-21 Thread Simon Peyton-Jones

| > | ps: you successfully going through all the standard Haskell
troubles
| > in
| > | this area :)  seems that making FAQ about using ST monad will be a
| > | good idea :)
| 
| > Indeed. If someone would like to start one, a good place for it
would be
| > GHC's collaborative-documentation Wiki
| >
http://haskell.org/haskellwiki/GHC#Collaborative_documentation
| 
| they are not ghc-specific, afaik

Some aspects are -- e.g. the behaviour of higher-rank types.   But by
all means attach it somewhere else

S


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


Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-21 Thread Jon Fairbairn
On 2006-07-20 at 18:31BST I wrote:
> On 2006-07-13 at 10:16BST I wrote:
> > Hooray!  I've been waiting to ask "Why aren't we asking what
> > laws hold for these operations?"
> 
> Having thought about this for a bit, I've come up with the
> below. This is intended to give the general idea -- it's not
> polished code,

And already some changes (but all to comments) I'd
appreciate comments on the law below.

--- lib/split.lhs   2006/07/21 08:54:28 1.1
+++ lib/split.lhs   2006/07/21 09:42:49
@@ -17,10 +17,17 @@

   => "A Random List Of Words\nOn Lines"

+  I think the relevant law is
+  (forall x. all (not . p) (map f x)) =>
+  segmentsSatisfying (not . p) . fromParts . mapRight f . parts p
+  == segmentsSatisfying (not . p)
+
+  In other words, if f doesn't add any "not . p" elements,
+  the segments satisfying "not . p" are unchanged.

 > contiguousParts p l = [a | Right a <- parts p l]

-  so words = contiguousParts Char.isAlphaNum
+  so words = contiguousParts (not . Char.isSpace)

 > segmentsSatisfying predicate
 > = concat . map dropSeps . parts predicate

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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