Re: main modules in GHC, deriving differences between GHC and Hugs

2003-06-13 Thread Wolfgang Jeltsch
On Friday, 2003-06-13, 22:06, CEST, Hal Daume III wrote:
> [...]

> Personally, I think this is stupid and that you should be able to compile
> any module with a 'main :: IO a' function as an executable without having to
> call it Main.

> [...]

I would even say that you should be able to use a "main variable" which is not 
named "main". You would have to specify its identifier at the command line. 
But I wouldn't allow arbitrary IO a types but only IO ().

>  - Hal

Wolfgang

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Typesafe MRef with a regular monad

2003-06-13 Thread Carl R. Witty
Keith Wansbrough <[EMAIL PROTECTED]> writes:

> > In article <[EMAIL PROTECTED]>,
> >  [EMAIL PROTECTED] (Carl R. Witty) wrote:
> > 
> > > Here's a hand-waving argument that you need either Typeable (or
> > > something else that has a run-time concrete representation of types)
> > > or ST/STRef (or something else, probably monadic, that can track
> > > unique objects) to do this.
> > 
> > George Russell already showed this, didn't he? You can implement 
> > Typeable given type-safe MRefs, and you can implement type-safe MRefs 
> > given Typeable.
> 
> But George Russell's implementation relied on looking up something in
> one map with a key obtained from another map.  I thought type-safe
> MRefs should disallow this.

If you use Simon PJ's type signatures, you can't really disallow using
a key from one map with another map.

Carl Witty
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: main modules in GHC, deriving differences between GHC and Hugs

2003-06-13 Thread Hal Daume III
Yes, but there's a problem with this solution.  Namely, if Foo.hs takes a
long time to compile, then you can't leverage having already created Foo.o
and Foo.hi when making the Main.

The solution I use is a script that you call like:

  ghcmake File

which creates MainXXX.hs (where XXX is a random number) and this contains:

  module Main where { import qualified File (main) ; main = File.main }

It then runs ghc --make on that and deletes the MainXXX.hs file.

This works okay, but isn't very satisfactory.

Personally, I think this is stupid and that you should be able to compile
any module with a 'main :: IO a' function as an executable without having
to call it Main.  You can probably find a message from me to this extent
in the archives, as well as some response.

 - Hal

--
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

On Fri, 13 Jun 2003, Matthew Donadio wrote:

> Graham Klyne wrote:
> > GHC seems to require a 'main' module in a file in order to generate an exe
> > file.   This makes it awkward to create unit test programs, because I
> > generally create one (to run stand-alone) for each major module.  Now I
> > want to create a "master test" module that runs all the individual module
> > tests.  But if the module tests are all "main" modules it seems I cannot
> > bring them all together into a larger program.  Have I overlooked any way
> > to create an executable program from any module containing a main function
> > of the appropriate type?
> 
> The easiest way to handle this is to run all the source through the C
> preprocessor, and put #ifdef's around main and the module name. 
> Something like
> 
> #ifdef UNIT_TEST
> module Main where
> #else
> module Foo where
> #endif
> 
> foo x y = x + y
> 
> tests = [ foo 2 3 == 5, 
>   foo 3 4 /= 6
> ]
> 
> #ifdef UNIT_TEST
> main = print $ and tests
> #else
> foo_test = and tests
> #endif
> 
> I haven't done this with Haskell, but I have done it with a lot of my C
> libraries.
> 
> -- 
> Matthew Donadio ([EMAIL PROTECTED])
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: main modules in GHC, deriving differences between GHC and Hugs

2003-06-13 Thread Matthew Donadio
Graham Klyne wrote:
> GHC seems to require a 'main' module in a file in order to generate an exe
> file.   This makes it awkward to create unit test programs, because I
> generally create one (to run stand-alone) for each major module.  Now I
> want to create a "master test" module that runs all the individual module
> tests.  But if the module tests are all "main" modules it seems I cannot
> bring them all together into a larger program.  Have I overlooked any way
> to create an executable program from any module containing a main function
> of the appropriate type?

The easiest way to handle this is to run all the source through the C
preprocessor, and put #ifdef's around main and the module name. 
Something like

#ifdef UNIT_TEST
module Main where
#else
module Foo where
#endif

foo x y = x + y

tests = [ foo 2 3 == 5, 
  foo 3 4 /= 6
]

#ifdef UNIT_TEST
main = print $ and tests
#else
foo_test = and tests
#endif

I haven't done this with Haskell, but I have done it with a lot of my C
libraries.

-- 
Matthew Donadio ([EMAIL PROTECTED])
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


main modules in GHC, deriving differences between GHC and Hugs

2003-06-13 Thread Graham Klyne
GHC seems to require a 'main' module in a file in order to generate an exe 
file.   This makes it awkward to create unit test programs, because I 
generally create one (to run stand-alone) for each major module.  Now I 
want to create a "master test" module that runs all the individual module 
tests.  But if the module tests are all "main" modules it seems I cannot 
bring them all together into a larger program.  Have I overlooked any way 
to create an executable program from any module containing a main function 
of the appropriate type?

There also seems to be a difference in the way that GHC and Hugs handle 
deriving clauses.  I haven't pinned this down, but I can try to provide 
more information if this is something the compiler developers not already 
aware of.

#g

---
Graham Klyne
<[EMAIL PROTECTED]>
PGP: 0FAA 69FF C083 000B A2E9  A131 01B9 1C7A DBCA CB5E
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Typesafe MRef's

2003-06-13 Thread George Russell
Keith Wansbrough wrote (snip)
No, because update should not return a new key, it should update the 
value of the same key.  In other words,

let (m1,k) = insert empty "A"
m2 = update m1 k "B"
in
lookup m2 k
should give "B", not "A", just like with MRefs.
So what does the function
   insert2 val1 val2 =
  let
 (m1,k1) = insert empty (Just val1)
 (m2,k2) = insert m1 (Just val2)
 m3 = update m2 k1 Nothing
  in
 isJust (lookup m3 k2)
return?  It looks to me as if it returns True if val1 and val2 have
different types, False if they have the same type.  So you have now
got a way of comparing two types for equality, and so a rather
roundabout reimplementation of Dynamic.


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Threads

2003-06-13 Thread Hal Daume III
Presumably you need a call to yield or threadDelay or something like that.

--
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

On Fri, 13 Jun 2003, Filip wrote:

> Hi,
> 
> I have function
> f:: a -> b
> 
> and I need something like this:
> 
> myaccept:: Socket ->  IO ()
> myaccept g = do a <- accept g
>  t <- forkIO (f a)
>  myaccept g
> 
> What to do to have two threads working at the same time. When I am using myaccept, 
> program is suspending.
> 
> Thanks.
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Threads

2003-06-13 Thread Filip
Hi,

I have function
f:: a -> b

and I need something like this:

myaccept:: Socket ->  IO ()
myaccept g = do a <- accept g
 t <- forkIO (f a)
 myaccept g

What to do to have two threads working at the same time. When I am using myaccept, 
program is suspending.

Thanks.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Typesafe MRef's

2003-06-13 Thread Keith Wansbrough
> Keith wrote (snipped)
>  > But George Russell's implementation relied on looking up something in
>  > one map with a key obtained from another map.  I thought type-safe
>  > MRefs should disallow this.
> 
> However if you disallow lookup up in one map with a key from another,
> then Ralf Hinze's solution of putting the value inside the key
> uses no type extentions and works perfectly well (though is probably
> not quite what was intended).

No, because update should not return a new key, it should update the 
value of the same key.  In other words,

let (m1,k) = insert empty "A"
m2 = update m1 k "B"
in
lookup m2 k

should give "B", not "A", just like with MRefs.

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: problems with working with Handles

2003-06-13 Thread Tomasz Zielonka
On Fri, Jun 13, 2003 at 10:57:21AM -0400, Dean Herington wrote:
> Tomasz Zielonka wrote:
> 
> > One can also use Strategies module that comes with GHC (in package
> > concurrent), for example:
> 
> Could you tell me more specifically where to find the Strategies module in
> GHC?  I couldn't find it in the documentation.

[EMAIL PROTECTED] load]$ ghci -package concurrent
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.0, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Loading package concurrent ... linking ... done.
Prelude> :m + Strategies
Prelude Strategies> :m + IO
Prelude Strategies IO> h <- openFile "/etc/termcap" ReadMode
Prelude Strategies IO> cs <- hGetContents h
Prelude Strategies IO> putStrLn "hmm" `demanding` rnf cs
hmm
Prelude Strategies IO> hClose h
Prelude Strategies IO> length cs
737535
Prelude Strategies IO>

Note that you have to use -package Strategies option. I couldn't find
this module in the hierarchical libraries. The same works in GHC 5.04.3

To GHC developers:
What is the status of this module?
Can I assume that future versions of GHC will have it?

> Thanks.
> Dean

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Typesafe MRef's

2003-06-13 Thread Ralf Hinze
Am Freitag, 13. Juni 2003 17:12 schrieb George Russell:
> Keith wrote (snipped)
>
>  > But George Russell's implementation relied on looking up something in
>  > one map with a key obtained from another map.  I thought type-safe
>  > MRefs should disallow this.
>
> However if you disallow lookup up in one map with a key from another,
> then Ralf Hinze's solution of putting the value inside the key
> uses no type extentions and works perfectly well (though is probably
> not quite what was intended).

Here is the modified version of `update':

 update   :: (Typable b) => FM k -> Key k a -> a -> FM k
 update (FM bs) (Key k r) b   =  FM ((k, Dyn r b) : bs)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Typesafe MRef's

2003-06-13 Thread George Russell
Keith wrote (snipped)
> But George Russell's implementation relied on looking up something in
> one map with a key obtained from another map.  I thought type-safe
> MRefs should disallow this.
However if you disallow lookup up in one map with a key from another,
then Ralf Hinze's solution of putting the value inside the key
uses no type extentions and works perfectly well (though is probably
not quite what was intended).
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: problems with working with Handles

2003-06-13 Thread Tomasz Zielonka
On Fri, Jun 13, 2003 at 10:34:53AM -0400, Dean Herington wrote:
> 
> `seq` guarantees only enough evaluation to determine whether its first
> argument is bottom.  That's why your commented code reads only the first
> character.  You need to evaluate the entire string.  As someone else
> suggested, `deepSeq` is one way to do this.  I've appended the current
> version of my DeepSeq module to this reply.

One can also use Strategies module that comes with GHC (in package
concurrent), for example:

y `demanding` rnf x

will Reduce x to Normal Form, before evaluating y. I hope I got this
right :)

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: problems with working with Handles

2003-06-13 Thread Dean Herington
Niels Reyngoud wrote:

> Hello all,
>
> Thanks for your replies on our previous posts. To avoid the lazy
> behaviour, we tried to write our own IO module "IOExts2" which basically
> redifnes
> readFile, writeFile and appendFile to make sure they use binary-mode and
> strict behaviour. The libary is as follows:
>
> --
> module IOExts2(readFile', writeFile', appendFile') where
>
> import IO
> import IOExts
>
> readFile' :: String -> IO String
> readFile' inputfile = do readhandle <- openFileEx inputfile (BinaryMode
> ReadMode)
>  x <- hGetContents readhandle
>  seq x (return x)
>{-  seq x (do hClose readhandle
>return x) -}

`seq` guarantees only enough evaluation to determine whether its first
argument is bottom.  That's why your commented code reads only the first
character.  You need to evaluate the entire string.  As someone else
suggested, `deepSeq` is one way to do this.  I've appended the current
version of my DeepSeq module to this reply.

> writeFile' :: String -> String -> IO()
> writeFile' outputfile text = seq text (writeFile'' outputfile text)
>
> writeFile'' :: String -> String -> IO()
> writeFile'' outputfile text = do writehandle <- openFileEx outputfile
> (BinaryMode WriteMode)
>  hPutStr writehandle text
>   hFlush writehandle
> hClose writehandle
>
> appendFile' :: String -> String -> IO()
> appendFile' outputfile text = seq text (appendFile'' outputfile text)
>
> appendFile'' :: String -> String -> IO()
> appendFile'' outputfile text = do appendhandle <- openFileEx outputfile
> (BinaryMode AppendMode)
>   hPutStr appendhandle text
>   hFlush appendhandle
>   hClose appendhandle

Output is not done lazily, so use of `seq` in the above is superfluous.

> ---
>
> Yet, there's still one problem left with readFile'. The handles of
> appendFile' and writeFile' are properly closed, but when I try to close
> the handle used for reading (as shown by the parts
> commented above) and try the following small test, which uses a file
> "123.txt"  that consists of the string "blaat" only a "b" is outputted.
> When  I do not close the handle, the entire string "blaat" is outputted.
>
> test = do x <- readFile' "123.txt"
>   putStr x
>
> Regards,
> Niels Reyngoud

DeepSeq.lhs  --  deep strict evaluation support

The `DeepSeq` class provides a method `deepSeq` that is similar to
`seq` except that it forces deep evaluation of its first argument
before returning its second argument.

Instances of `DeepSeq` are provided for Prelude types.  Other
instances must be supplied by users of this module.

$Id: DeepSeq.lhs,v 1.5 2002/04/01 20:58:24 heringto Exp $

> module  DeepSeq  where

> class  DeepSeq a  where  deepSeq :: a -> b -> b

> infixr 0 `deepSeq`, $!!

> ($!!) :: (DeepSeq a) => (a -> b) -> a -> b
> f $!! x = x `deepSeq` f x


> instance  DeepSeq ()  where  deepSeq = seq

> instance  DeepSeq Bool  where  deepSeq = seq
> instance  DeepSeq Char  where  deepSeq = seq

> instance  (DeepSeq a) => DeepSeq (Maybe a)  where
>   deepSeq Nothing  y = y
>   deepSeq (Just x) y = deepSeq x y

> instance  (DeepSeq a, DeepSeq b) => DeepSeq (Either a b)  where
>   deepSeq (Left  a) y = deepSeq a y
>   deepSeq (Right b) y = deepSeq b y

> instance  DeepSeq Ordering  where  deepSeq = seq

> instance  DeepSeq Int   where  deepSeq = seq
> instance  DeepSeq Integer   where  deepSeq = seq
> instance  DeepSeq Float where  deepSeq = seq
> instance  DeepSeq Doublewhere  deepSeq = seq

> instance  DeepSeq (a -> b)  where  deepSeq = seq

> instance  DeepSeq (IO a)  where  deepSeq = seq

> instance  (DeepSeq a) => DeepSeq [a]  where
>   deepSeq [] y = y
>   deepSeq (x:xs) y = deepSeq x $ deepSeq xs y

> instance  (DeepSeq a,DeepSeq b) => DeepSeq (a,b)  where
>   deepSeq (a,b)   y = deepSeq a $ deepSeq b y
> instance  (DeepSeq a,DeepSeq b,DeepSeq c) => DeepSeq (a,b,c)  where
>   deepSeq (a,b,c) y = deepSeq a $ deepSeq b $ deepSeq c y
> instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d) => DeepSeq (a,b,c,d)
where
>   deepSeq (a,b,c,d)   y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d y
> instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e) => DeepSeq
(a,b,c,d,e)  where
>   deepSeq (a,b,c,d,e) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e y
> instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e,DeepSeq f) =>
DeepSeq (a,b,c,d,e,f)  where
>   deepSeq (a,b,c,d,e,f)   y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e $ deepSeq f y
> instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e,DeepSeq
f,DeepSeq g) => DeepSeq (a,b,c,d,e,f,g)  where
>   deepSeq (a,b,c,d,e,f,g) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq
d $ deepSeq e $ deepSeq f $ deepSeq g y

--end--

___

Re: a dream of databases

2003-06-13 Thread Alastair Reid
On Friday 13 June 2003 3:02 am, John Meacham wrote:
> so, I have been wanting to implement serialize to database functionality
> for haskell in a certain way which may or may not be possible..
>
> what would be nice is if I could dump an entire complex haskell data
> structure (perhaps cyclic, but not infinite) to a hash-table database [..]

This comes up every now and then.  The lack of an existing library to do 
anything like this is because there's a bunch of tricky issues to deal with.

It seems that to get anywhere with this, you have to decide not to deal with 
some of the following:

1) Writing unevaluated thunks out
(your 'not infinite' comment above suggests you have already
   dropped this).

2) Writing out datastructures which contain functions:

data T = App (T  -> T) T | Const Int

3) Writing out partial applications like 'Prelude.foldr (:) Nil'.

[2 and 3 lead to problems establishing function identity and 
versioning problems. 
For example, when you read that back in, will you assume that it means
the version of Prelude.foldr provided by your compiler or will you need to 
read the function (in source-, intermediate- or machine- code)?
Partial applications involving locally defined functions are especially tricky 
since we don't have a natural 'name' we can use to identify them.]

4) Versioning issues caused by change of compiler options or change of
compiler version, or change of compiler.
e.g., if I compile the code with -O2 and then try to read it into
a program compiled with -O

5) Versioning issues caused by change in source code.
   e.g., if I write it out, add a new constructor to a datatype and recompile.
   e.g., if I write it out of one program and read it into another.

[4 and 5 together amount to asking 'How do you decide if two types are the 
same?  Haskell provides an answer for two types in a single program or 
translation unit but things get hazy when you have two programs, etc.]

6) Making sharing too observable.

   When you talk about writing cyclic datastructures out, you are
   talking about a  property (i.e., sharing) of Haskell datastructures
   which varies between compilers
   and might even vary with level of optimization.

   I think what you mean is that you would like the property that a
   (fully evaluated) data structure which consumes finite heap space
   should require finite disk space.  Indeed, we'd like the space to be
   at most a constant factor bigger.

  This amounts to the same thing but doesn't require us to delve into 
  black holes like defining when sharing happens in Haskell implementations.

There's probably a few more details...

--
Alastair Reid
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: problems with working with Handles

2003-06-13 Thread Wolfgang Jeltsch
On Friday, 2003-06-13, 10:33, CEST, Niels Reyngoud wrote:
> [...]

> To avoid the lazy behaviour, we tried to write our own IO module "IOExts2"
> which basically redifnes readFile, writeFile and appendFile to make sure
> they use binary-mode and strict behaviour. The libary is as follows:
>
> [...]
>
> readFile' :: String -> IO String
> readFile' inputfile = do readhandle <- openFileEx inputfile (BinaryMode
> ReadMode)
>  x <- hGetContents readhandle
>  seq x (return x)

Are you sure you want seq and not deepSeq?

> [...]

Wolfgang

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: what dreams may come ...

2003-06-13 Thread Jon Awbrey
o~o~o~o~o~o

john, with no particular reference to haskell,
but just generically speaking, this sounds
vaguely similar to what i worked on all
through the 80's in lisp and pascal,
when ut-lisp used to pull a hal 9k
about cyclic d-structures so i had
to start redoing everything from
scratch on my own recognizance
in turbo pascal, no really.
vide my recent, very slow
attempts to document this
work at my inquiry list:

http://stderr.org/pipermail/inquiry/
http://stderr.org/cgi-bin/mailman/listinfo/inquiry

here are the anchors of some pertinent threads:

http://stderr.org/pipermail/inquiry/2003-March/000100.html -- exposition
http://stderr.org/pipermail/inquiry/2003-March/000115.html -- source code
http://stderr.org/pipermail/inquiry/2003-March/000120.html -- commentary
http://stderr.org/pipermail/inquiry/2003-March/000141.html -- motivation

it may be another year or so before i can finish (or even get back to)
the te deums of documentality, but if anybody is remotely tantalized
i will do my level best to explain what's going on there.

jon awbrey

o~o~o~o~o~o

> Message: 10
> Date: Thu, 12 Jun 2003 19:02:55 -0700
> From: John Meacham <[EMAIL PROTECTED]>
> Subject: a dream of databases
> To: [EMAIL PROTECTED]
> 
> so, I have been wanting to implement serialize to database functionality
> for haskell in a certain way which may or may not be possible..
> 
> 
> what would be nice is if I could dump an entire complex haskell data
> structure (perhaps cyclic, but not infinite) to a hash-table database
> (like berkeley db). pointers would be swizzled into hash keys and each
> haskell thunk would become an entry in the database.
> 
> loading the database would return the haskell structure just as it was
> put into the database but it would be demand loaded. meaning that
> evaluating a data thunk will actually grab that entry out of the
> database (like with lazy file reading) and entries that have not been
> accessed in a while would be transparently reclaimed by the garbage
> collector (and reloaded later if needed)
> 
> And of course, these haskell data structures should be albe to be
> arbitrary and would look no different from other haskell data
> structures. they would just have appropriate instances derived for them
> by DrIFT (or perhaps template haskell).
> 
> now. I am pretty sure I can do the demand loading bit with some
> goddawful code (inspired by HOODs internals) using unsafePerformIO and
> Weak pointers in truly nefarious ways. The dumping to the database bit
> is straightforward when working with trees. but I can't figure out a way
> to do it for potentially complex datastructures. perhaps someone out
> there has an idea? perhaps some template haskell tricks can be pulled to
> make it happen? I realize that any solution will be quite hacky and
> unlikely to be very portable.
> 
> John
> 
> ---
> John Meacham - California Institute of Technology, Alum. - [EMAIL PROTECTED]
> ---
o~o~o~o~o~o

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: ghc6.0 and ghc5.04.3 i386 rpms available

2003-06-13 Thread Jens Petersen
2003年06月13日(金)の17時53分に Jens Petersen 曰く:
> The latest package is named
> ghc6.0-6.0-1 and there is also a ghc5.04.3-5.04.3-2 package[...] The
> ghc5.04.3 and ghc6.0 can be installed in parallel without conflicts,

Thinking about it more, I realised that of course what is really being
numbered here is the interface version number of the hi files (the "ABI"
version if you like), so perhaps it would be better to name the packages
ghc6000 and ghc5043?  These names also seems a little more seemly...

Opinions?

Jens

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Problems with working with Handles (PS)

2003-06-13 Thread Simon Marlow
 
> (moderator, can you please include this mail at the bottom of my 
> previous mail?)
> 
> PS: I think the next example shows pretty well what goes wrong when 
> you're not closing the read-handle:
> 
> ---
> test = do writeFile' "123.txt" "blaat"
> 
>  appendFile' "123.txt" " 1"
>  z <- readFile' "123.txt"
> 
>  appendFile' "123.txt" " 2"
>  s <- readFile' "123.txt"
>  appendFile' "123.txt" " 3"
>  t <- readFile' "123.txt"
>  putStr ("\n\n")
>  putStr (z ++ "\n" ++ s ++ "\n" ++ t)
> 
> ---
> 
> Instead of "blaat 1
> blaat 1 2
>  blaat 1 2 3"
> 
> three lines of "blaat 1 2 3" are outputted.

Note that on a conforming Haskell 98 system, the above program (with the
primes deleted) will fail.  For example, GHC responds:

Fail: resource busy
Action: openFile
Reason: file is locked
File: 123.txt

This is because Haskell 98 specifies that the IO system should implement
multiple-reader/single-writer locks on a per-file basis.

Cheers,
Simon

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


ADV: Haskell-related postdoc positions at Chalmers University

2003-06-13 Thread John Hughes

Post-doctoral Fellowships at Chalmers University


We are seeking one or two postdoctoral research fellows to work at the
Department of Computing Science on the CoVer project (COmbining
VERification methods), a collaboration between the functional
programming, formal methods, and programming logic groups. The goal of
the project is to integrate testing and formal verification methods in
a program development environment for Haskell programs. We have been
awarded 8MSEK (about 870,000 euros) by the Swedish Foundation for
Strategic Research to fund this work. The project leaders are John
Hughes, Mary Sheeran, Peter Dybjer, and Thierry Coquand.

We are looking for well qualified candidates with a recent doctorate
in a related area, and with proven system building skills, to spend up
to two years with us as Research Fellows. We are looking for
candidates familiar with some or all of these areas:

* functional programming, especially using Haskell
* dependent types and logic
* proof editors
* automated theorem provers
* program analysis and transformation

Responsibilities will include system development in Haskell.

Further information on the CoVer project is available at

http://dilbert.cs.chalmers.se/Cover/

Successful applicants will receive a tax-free fellowship of around
16,000 SEK per month (about 1,750 euros), which is sufficient to live
comfortably in Göteborg. Swedish tax law restricts these fellowships
to people coming from abroad: those presently working in Sweden are
not eligible. Start date is negotiable from 1 September to 1 January
2004.

Gothenburg is an attractive city on the Swedish west coast, offering
an excellent quality of life. It has all the cultural amenities you
would expect of Sweden's second city, and the easy access to unspoiled
nature of a country with less than 10% the population density of the
UK! A good starting point for information on the city is

http://www.goteborg.com/default.asp?id=4293

Candidates are welcome to contact any of the Principal Investigators
with questions. Please email an application letter, together with your
CV and a copy of *one* relevant publication to [EMAIL PROTECTED],
by Sunday June 29th at the latest. Your application letter should
specifically address your system building skills as well as your
research experience. Attached documents should be Postscript or PDF.

John Hughes [EMAIL PROTECTED]
Mary Sheeran[EMAIL PROTECTED]
Peter Dybjer[EMAIL PROTECTED]
Thierry Coquand [EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Problems with working with Handles (PS)

2003-06-13 Thread Niels Reyngoud
(moderator, can you please include this mail at the bottom of my 
previous mail?)

PS: I think the next example shows pretty well what goes wrong when 
you're not closing the read-handle:

---
test = do writeFile' "123.txt" "blaat"
appendFile' "123.txt" " 1"
z <- readFile' "123.txt"
appendFile' "123.txt" " 2"
s <- readFile' "123.txt"
appendFile' "123.txt" " 3"
t <- readFile' "123.txt"
putStr ("\n\n")
putStr (z ++ "\n" ++ s ++ "\n" ++ t)
---

Instead of "blaat 1
   blaat 1 2
blaat 1 2 3"
three lines of "blaat 1 2 3" are outputted. The strange thing is that 
using "putStr z", "putStr s", and "putStr t" after each call of 
readFile' solves the problem,
but using seq (even though it's already called in the function readFile' 
in our module). before appending a new character to the file, like "seq 
z (appendFile "123.txt" "2")
doesn't work.

Best regards,
Niels Reyngoud
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: problems with working with Handles

2003-06-13 Thread Niels Reyngoud
Hello all,

Thanks for your replies on our previous posts. To avoid the lazy 
behaviour, we tried to write our own IO module "IOExts2" which basically 
redifnes
readFile, writeFile and appendFile to make sure they use binary-mode and 
strict behaviour. The libary is as follows:

--
module IOExts2(readFile', writeFile', appendFile') where
import IO
import IOExts
readFile' :: String -> IO String
readFile' inputfile = do readhandle <- openFileEx inputfile (BinaryMode 
ReadMode)
x <- hGetContents readhandle
seq x (return x)
  {-  seq x (do hClose readhandle
  return x) -}


writeFile' :: String -> String -> IO()
writeFile' outputfile text = seq text (writeFile'' outputfile text)
writeFile'' :: String -> String -> IO()
writeFile'' outputfile text = do writehandle <- openFileEx outputfile 
(BinaryMode WriteMode)
hPutStr writehandle text
 hFlush writehandle
   hClose writehandle

appendFile' :: String -> String -> IO()
appendFile' outputfile text = seq text (appendFile'' outputfile text)
appendFile'' :: String -> String -> IO()
appendFile'' outputfile text = do appendhandle <- openFileEx outputfile 
(BinaryMode AppendMode)
 hPutStr appendhandle text
 hFlush appendhandle
 hClose appendhandle

---

Yet, there's still one problem left with readFile'. The handles of 
appendFile' and writeFile' are properly closed, but when I try to close 
the handle used for reading (as shown by the parts
commented above) and try the following small test, which uses a file 
"123.txt"  that consists of the string "blaat" only a "b" is outputted. 
When  I do not close the handle, the entire string "blaat" is outputted.

test = do x <- readFile' "123.txt"
 putStr x
Regards,
Niels Reyngoud
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Typesafe MRef with a regular monad

2003-06-13 Thread Keith Wansbrough
> In article <[EMAIL PROTECTED]>,
>  [EMAIL PROTECTED] (Carl R. Witty) wrote:
> 
> > Here's a hand-waving argument that you need either Typeable (or
> > something else that has a run-time concrete representation of types)
> > or ST/STRef (or something else, probably monadic, that can track
> > unique objects) to do this.
> 
> George Russell already showed this, didn't he? You can implement 
> Typeable given type-safe MRefs, and you can implement type-safe MRefs 
> given Typeable.

But George Russell's implementation relied on looking up something in
one map with a key obtained from another map.  I thought type-safe
MRefs should disallow this.

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: a dream of databases

2003-06-13 Thread Keith Wansbrough
> now. I am pretty sure I can do the demand loading bit with some
> goddawful code (inspired by HOODs internals) using unsafePerformIO and
> Weak pointers in truly nefarious ways. The dumping to the database bit
> is straightforward when working with trees. but I can't figure out a way
> to do it for potentially complex datastructures. perhaps someone out
> there has an idea? perhaps some template haskell tricks can be pulled to
> make it happen? I realize that any solution will be quite hacky and
> unlikely to be very portable.

You probably want to use unsafePtrEq, and possibly something to give
you a hash of a pointer... or maybe you want to look at Koen
Claessen's "observable sharing" work that he developed for Lava.

  http://www.math.chalmers.se/~koen/Papers/obs-shar.ps

--KW 8-)

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


ghc6.0 and ghc5.04.3 i386 rpms available

2003-06-13 Thread Jens Petersen
Hello,

Recently I have made some further small packaging improvements to the
ghc-6.0 rpms announced earlier.  The latest package is named
ghc6.0-6.0-1 and there is also a ghc5.04.3-5.04.3-2 package (using the
same patch as the ghc-5.04.3-1 package for RHL9 made by Andy Moran). The
ghc5.04.3 and ghc6.0 can be installed in parallel without conflicts,
since I separated out the utils programs into -utils subpackages.  They
are all available from

  http://haskell.org/~petersen/rpms/ghc/

I have tested them both on Red Hat Linux 8.0 and 9.  (The new packages
names are a little long, but this means that when say ghc-6.1 comes out
there won't been a need to generate a ghc6.0 then, but just a ghc6.1
package...)

Please try them and let me know what you think or if you have any
problems.  There is also ChangeLog file in the above directory too, so
that one can easily see what changes have been made between the
different package releases.

Cheers, Jens


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell