a newbie's question about something related to runST

2000-04-26 Thread Jan Brosius



Hi,

First I give the following primitive 
operations
 
 newVar :: a 
- ST s (MutVar s a)
 
 readVar :: MutVar 
s a - ST s a

 writeVar :: MutVar 
s a -a - ST s ()

Next consider the function

 f :: MutVar s a 
- Mut Var s a
 

 f v = runST 
(newVar v `thenST` \w -
 

 
readVar w)

1. What is the type given to newVar v by 
the typechecker?






Friendly

Jan Brosius



How to debug Haskell programs?

2000-04-26 Thread Friedrich Dominicus

This question may sound a bit strange. I'll try to explain. I have
written a piece of Haskell and found that I did not understand
things. I tried to look what I got wrong and searched for a
possibility to give me output. Now obvious is that Haskell has not
debugger so I was thinking helping myself with adding some simple
output stuff but that did not seem to work either. So guess I have

sum:: [Int] - Int
sum [] = 0
sum (x:xs) = 

Now how can I do the following print the actual sum in every step and
how to see e.g what x or xs is on this step?

I tried it with simple ouput but did not get it right.

Any suggestions?
Friedrich




Re: a newbie's question about something related to runST

2000-04-26 Thread Fergus Henderson

On 26-Apr-2000, Jan Brosius [EMAIL PROTECTED] wrote:
 Hi,
 
 First I give the following primitive operations

   newVar  :: a - ST s (MutVar s a)
   
   readVar :: MutVar s a  -  ST s a
 
   writeVar :: MutVar s a - a - ST s ()
 
 Next consider the function
 
   f :: MutVar s a - Mut Var s a
 
   f v = runST (newVar v `thenST` \w -

   readVar w)
 
 1. What is the type given to newVar v  by the typechecker?

Let's see... `v' has type `MutVar s a', and after renaming apart
`newVar' has type `forall a2,s2 . a2 - ST s2 (MutVar s2 a2)',
so, substituting `Mutvar s a' for `a2', we see that
`newVar v' has type `forall s2 . ST s2 (MutVar s2 (MutVar s a))'.

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.




Re: How to debug Haskell programs?

2000-04-26 Thread Lars Lundgren

On 26 Apr 2000, Friedrich Dominicus wrote:

 This question may sound a bit strange. I'll try to explain. I have
 written a piece of Haskell and found that I did not understand
 things. I tried to look what I got wrong and searched for a
 possibility to give me output. Now obvious is that Haskell has not
 debugger so I was thinking helping myself with adding some simple
 output stuff but that did not seem to work either. So guess I have
 
 sum:: [Int] - Int
 sum [] = 0
 sum (x:xs) = 
 
 Now how can I do the following print the actual sum in every step and
 how to see e.g what x or xs is on this step?
 
 I tried it with simple ouput but did not get it right.
 
 Any suggestions?
 Friedrich
 


import IOExts

sum:: [Int] - Int
sum [] = 0
sum (x:xs) = trace (show (x:xs) ++ "\n") 


Note, this is an unpure extension to haskell that should be used for
debugging purposes only. It can sometimes be very hard to interpret the
output since it will be produced in the order the expressions are
evaluated.

Anyway, it is sometimes useful.

/Lars L






basAlgPropos

2000-04-26 Thread S.D.Mechveliani

Fergus Henderson [EMAIL PROTECTED]
writes on my letter on Basic algebra proposal


 These features are not mandatory in proposal. The jury may decide to
 rewrite the proposal removing the usage of these features.
 [..].

 I think the "jury" is unlikely to rewrite the proposal;
 more likely, they will simply reject the proposal.
 It is up to the proponent(s) of the proposal to rewrite it.


It needs clarification.
The Proposal says that it is draft.
I thought that some committee, - which I called "jury"
(maybe, wrongly), - has to consider it.
If the committee decides that it is too hard to revise the proposal
to something satisfactory, it tells the author that the proposal is
rejected.
Otherwise, it recommends the author in what way to revise the
proposal, and after the revision, considers it again.
This was my naive idea of considering the library standard.
The committee may be official or in-formal, it may consist of a 
sidle person or of 1000, I do not know. 
But I had to refer to it in a letter, somewhat call it. 

I have no idea of how such committee may appear.
Neither do I care much of what with this proposal will happen.

--
Sergey Mechveliani
[EMAIL PROTECTED]














openfile :: String - String

2000-04-26 Thread Hamilton Richards

The Gofer prelude had a function

openfile :: String - String

which mapped file path names to strings containing the named files' contents.

The Hugs98 Prelude doesn't seem to have anything like that function.
Instead, it has things like

readFile :: String - IO String

Why would I want openfile instead of readFile? The problem in which the
need for openfile arose is this:

   I want to load a binary search tree and a list with
   words read from a file, and then perform, interactively,
   several tests comparing the cost of searching the
   tree with that of searching the list. In addition to
   performing the tests interactively, I want to separate
   the cost of searching the list and the tree from the
   cost of constructing them.

In order for the list and the tree to be used in several successive
command-line evaluations without being reconstructed each time, they must
be named globally. This is no problem with openfile, but readFile forces
their names to be local to an IO command.

Can anyone suggest a solution?

Thanks,

--Ham



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--






RE: openfile :: String - String

2000-04-26 Thread Chris Angus

You could try this:

--OpenFile.hs
module OpenFile where
import IOExts

openfile :: String - String
openfile =  unsafePerformIO . readFile
-- end of file

 -Original Message-
 From: Hamilton Richards [mailto:[EMAIL PROTECTED]]
 Sent: 26 April 2000 14:04
 To: [EMAIL PROTECTED]
 Subject: openfile :: String - String
 
 
 The Gofer prelude had a function
 
   openfile :: String - String
 
 which mapped file path names to strings containing the named 
 files' contents.
 
 The Hugs98 Prelude doesn't seem to have anything like that function.
 Instead, it has things like
 
   readFile :: String - IO String
 
 Why would I want openfile instead of readFile? The problem in 
 which the
 need for openfile arose is this:
 
I want to load a binary search tree and a list with
words read from a file, and then perform, interactively,
several tests comparing the cost of searching the
tree with that of searching the list. In addition to
performing the tests interactively, I want to separate
the cost of searching the list and the tree from the
cost of constructing them.
 
 In order for the list and the tree to be used in several successive
 command-line evaluations without being reconstructed each 
 time, they must
 be named globally. This is no problem with openfile, but 
 readFile forces
 their names to be local to an IO command.
 
 Can anyone suggest a solution?
 
 Thanks,
 
 --Ham
 
 
 
 --
 Hamilton Richards Jr.Department of Computer Sciences
 Senior Lecturer  Mail Code C0500
 512-471-9525 The University of Texas at Austin
 SHC 434  Austin, Texas 78712-1188
 [EMAIL PROTECTED]
 --
 
 
 




Re: openfile :: String - String

2000-04-26 Thread Lars Lundgren

On Wed, 26 Apr 2000, Hamilton Richards wrote:

 The Gofer prelude had a function
 
   openfile :: String - String
 
 which mapped file path names to strings containing the named files' contents.
 
 The Hugs98 Prelude doesn't seem to have anything like that function.
 Instead, it has things like
 
   readFile :: String - IO String
 
 Why would I want openfile instead of readFile? The problem in which the
 need for openfile arose is this:
 
I want to load a binary search tree and a list with
words read from a file, and then perform, interactively,
several tests comparing the cost of searching the
tree with that of searching the list. In addition to
performing the tests interactively, I want to separate
the cost of searching the list and the tree from the
cost of constructing them.
 
 In order for the list and the tree to be used in several successive
 command-line evaluations without being reconstructed each time, they must
 be named globally. This is no problem with openfile, but readFile forces
 their names to be local to an IO command.
 

Why is this a problem? After all, the names ARE dependent on IO.

 Can anyone suggest a solution?


I do not understand the problem.

Is it something like this you want?

parseTree :: String - Tree
parseList :: String - List

buildTree:: IO Tree
buildTree = do f - readFile "thetree"
   return (parseTree f)

buildList:: IO List
buildList = do f - readFile "thelist"
   return (parseList f)  

test :: IO()
test = do tree - buildTree
  list - buildList
  dowhateverYouwant_interactive_or_not tree list


dowhateverYouwant_interactive_or_not :: Tree - List - IO()

 
/Lars L







Re: a newbie's question about something related to runST

2000-04-26 Thread Jan Brosius




 On 26-Apr-2000, Jan Brosius [EMAIL PROTECTED] wrote:
  Hi,
 
  First I give the following primitive operations
 
newVar  :: a - ST s (MutVar s a)
 
readVar :: MutVar s a  -  ST s a
 
writeVar :: MutVar s a - a - ST s ()
 
  Next consider the function
 
f :: MutVar s a - Mut Var s a
 
f v = runST (newVar v `thenST` \w -
 
readVar w)
 
  1. What is the type given to newVar v  by the typechecker?

 Let's see... `v' has type `MutVar s a', and after renaming apart
 `newVar' has type `forall a2,s2 . a2 - ST s2 (MutVar s2 a2)',
 so, substituting `Mutvar s a' for `a2', we see that
 `newVar v' has type `forall s2 . ST s2 (MutVar s2 (MutVar s a))'.

 --

Ok, Next recall

 runST ::  forall s. (ST s a) - a

 and let  runST1 give the type signature

runST1 ::  ST s a  - a

consider

v = runST1 ( newVar True)

Then newVar True gets the type   ST s (MutVar s a)

( I prefer the more sloppy notation without a forall as it gives less
clutter).

In runST1 :: ST s a - a

Let us substitute a by  say  MutVar s a

we then get  after renaming the s in runST1 by s2

ST s2 ( MutVar s a ) - MutVar s a  )

Have we finished ? One would say no : one  needs  a substitution for s2 , If
we

don't "cheat"  we must now substitute s2  by s and we get

ST s (MutVar s) - MutVar s a

In principle this is not the type of  runST.

Because technically the "domain" of runST is of the form

ST s a  where a is never of the form T(s)

Finally consider

runST ::  forall s . ( ST s a) - a

What to do now ? let us first substitute  a by  MutVar s a   as shown above.

After renaming  there remains

 forall s2 . ( ST s2 (MutVar s a)) - MutVar s a

What is now the meaning of the forall s2  above?  If it means that s2 can be

substituted then we must substitute it by s But that is not what one wants :

one wants s2 to remain non free.


Where I wanted to come is this:

  give  runST the type signature


   runST :: exists s . ( ST s a ) - a

and technically we have also a bounded variable s. What is the reason for
choosing

forall  against  exists ? I think there is no reason for it. But I can be
wrong.

Friendly

Jan Brosius









Re: openfile :: String - String

2000-04-26 Thread John Atwood

Wy not load the list as program? E.g.
list1 =
 ["word1"
 ,"word2"
 ,"word3"
 ]
list2 = words "word1 word2 word3"
list3 = words
 "\
 \ word1\
 \ word2\
 \ word3\
 \"



John Atwood
-
Lars Lundgren wrote:
 
 On Wed, 26 Apr 2000, Hamilton Richards wrote:
 
  The Gofer prelude had a function
  
  openfile :: String - String
  
  which mapped file path names to strings containing the named files' contents.
  
  The Hugs98 Prelude doesn't seem to have anything like that function.
  Instead, it has things like
  
  readFile :: String - IO String
  
  Why would I want openfile instead of readFile? The problem in which the
  need for openfile arose is this:
  
 I want to load a binary search tree and a list with
 words read from a file, and then perform, interactively,
 several tests comparing the cost of searching the
 tree with that of searching the list. In addition to
 performing the tests interactively, I want to separate
 the cost of searching the list and the tree from the
 cost of constructing them.
  
  In order for the list and the tree to be used in several successive
  command-line evaluations without being reconstructed each time, they must
  be named globally. This is no problem with openfile, but readFile forces
  their names to be local to an IO command.
  
 
 Why is this a problem? After all, the names ARE dependent on IO.
 
  Can anyone suggest a solution?
 
 
 I do not understand the problem.
 
 Is it something like this you want?
 
 parseTree :: String - Tree
 parseList :: String - List
 
 buildTree:: IO Tree
 buildTree = do f - readFile "thetree"
return (parseTree f)
 
 buildList:: IO List
 buildList = do f - readFile "thelist"
return (parseList f)  
 
 test :: IO()
 test = do tree - buildTree
   list - buildList
   dowhateverYouwant_interactive_or_not tree list
 
 
 dowhateverYouwant_interactive_or_not :: Tree - List - IO()
 
  
 /Lars L
 
 
 
 
 





Re: openfile :: String - String

2000-04-26 Thread Hamilton Richards

At 3:18 PM +0200 4/26/00, Lars Lundgren wrote:
[...]

Is it something like this you want?

[...]

test :: IO()
test = do tree - buildTree
  list - buildList
  dowhateverYouwant_interactive_or_not tree list


dowhateverYouwant_interactive_or_not :: Tree - List - IO()

Sorry, I didn't make my problem clear enough.

The reason your suggestion doesn't solve it is that `tree` and `list` are
local to `test`, so they can't be used in several separate **command-line**
evaluations without being reconstructed each time. My students don't yet
know about interactive I/O; even if they did, I know of no way to get
separate reduction counts for, say, tree searches and list searches within
dowhateverYouwant_interactive_or_not.

But thanks anyway for taking the time to answer my ill-posed question.

Cheers,

--Ham



--
Hamilton Richards Jr.Department of Computer Sciences
Senior Lecturer  Mail Code C0500
512-471-9525 The University of Texas at Austin
SHC 434  Austin, Texas 78712-1188
[EMAIL PROTECTED]
--






Re: openfile :: String - String

2000-04-26 Thread Jan Skibinski


Angus is right on the track. I would only modify
it slightly:

content_xxx :: String
content_xxx = (unsafePerformIO . readFile) "xxx"

From Hugs perspective content_xxx is a constant.
Your may easily demonstrate it this way:

:!echo blah  xxx
content_xxx == "blah"
:!echo Hello  xxx
content_xxx == "blah"


Jan







Re: a newbie's question about something related to runST

2000-04-26 Thread Fergus Henderson

On 26-Apr-2000, Jan Brosius [EMAIL PROTECTED] wrote:
 
  runST ::  forall s. (ST s a) - a

It would be clearer to write that as

   runST ::  (forall s. ST s a) - a

rather than relying on the relative precedences
of `.' and `-'.

   give  runST the type signature
 
 
runST :: exists s . ( ST s a ) - a
 
 and technically we have also a bounded variable s. What is the reason for
 choosing
 
 forall  against  exists ?

`forall' means that the variable can be instantiated by the
caller, but not by the callee.
`exists' means the opposite, that the variable can be
instantiated by the callee, but not the caller.
If a function has a universally quantified type
such as `forall s . some type involving s',
then the function definition must be polymorphic in `s',
but the caller can call it with `s' bound to some
particular instance.  For `exists', it is the other way around,
the caller must be polymorphic in `s' but the function definition
could bind it to some particular instance.

If some Haskell implementation supported `exists' in that position,
and runST were declared with `exists' rather than `forall', then the
following example would be well-typed:

data MyStore = MyStore

side_effect :: STRef MyStore Int - Int - ()
side_effect ref new_val = runST arg
where
  arg :: exists s . ST s ()
  arg = clobber_it

  clobber_it :: ST MyStore ()
  clobber_it = writeSTRef ref new_val

Note here how the definition `arg = clobber_it'
binds the existentially quantified variable `s' to `MyStore'.
This allows the side effect to escape the ST monad.

You could then go ahead and use this nasty side_effect:

main = print (runST nasty)

nasty :: ST MyStore Int
nasty = do x - newSTRef 1
   dummy - newSTRef (side_effect x 42)
   readSTRef x

This might print either 1 or 42, depending on whether side
effect in the construction of the unused `dummy' variable
was optimized out.  Ouch!

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "I have always known that the pursuit
WWW: http://www.cs.mu.oz.au/~fjh  |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.