hugs / ghc difference over '(..)' imports

2002-02-17 Thread Duncan Coutts

There is a difference between hugs and ghc in how they treat imports with the 
'(..)' notation. Here's my example:

module CTree(
--other stuff
Const(..)
   ) where

import ATree (Const)

--const has constructors CInt, CChar, CStr

under hugs this module exports CInt, CChar, CStr
but under ghc it does not. Under ghc it only exports the constructors if I 
import 'Const' like this:

import ATree (Const(..))

I don't know which is the right behaviour w.r.t. the H98 standard, but it 
tripped me up.

Duncan
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



'Pretty' does not export ($+$)

2002-02-17 Thread Duncan Coutts


The pretty printing module 'Pretty' in the text package does not export the 
($+$) operator. The documentation says it does (and it certianly should).

I'm using ghc 5.02.1

Duncan
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Re: 'Pretty' does not export ($+$)

2002-02-17 Thread Sigbjorn Finne

Strange, the following compiles just fine with
5.02.1 on a Win2k box:

module Foo where { import Pretty ; x y = y Pretty.$+$ y }

--sigbjorn

- Original Message -
From: Duncan Coutts [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Sent: Sunday, February 17, 2002 16:13
Subject: 'Pretty' does not export ($+$)



 The pretty printing module 'Pretty' in the text package does not export
the
 ($+$) operator. The documentation says it does (and it certianly should).

 I'm using ghc 5.02.1

 Duncan


___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs



Strictness information?

2002-02-17 Thread Till Dörges

Hi folks,

during the struggle for speed of my program, I've tried to check the strictness of my 
functions, where most of the time is consumed. Unluckily the ghc documentation doesn't 
mention the strictness-types I found for the most part. :-(

For the particular function in question it reads in the *.hi file:

--- snip ---
isSubPosnOf :: Posn - Posn - PrelBase.Bool {-## __A 2 __C __S VV __U (__inline_me (\ 
a2 :: Posn b :: Posn - PrelBase.zaza (zddmzsze1 a2 b) (isPrefixOf b a2))) ##-};
--- snap ---

If I understand it correctly I must look at '__S VV', but what does V mean? (The doc 
only talks about L,S,E,P,U,A).

Thanks -- Till
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: The size of things

2002-02-17 Thread Ketil Z. Malde

Simon Marlow [EMAIL PROTECTED] writes:

 data STuple = STuple !Int Foo
 
 is slightly less efficient than using a normal tuple
 
 (Int,Foo)

 Just checking... with -funbox-strict-fields, right?

Yep.

 It's possible that the boxed Int is being reconstructed for some
 reason.  You'll be able to see the difference more accurately using
 heap profiling. 

Yeah, I guess I'll have to try to find an RPM where profiling works
properly.  (Time to upgrade to 5.02.2 anyway, isn't it.)

I guess I'll try to rewrite the whole thing using monadic arrays that
update in place.  But my nice algorithm is getting more and more
cluttered ... sigh.

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



haskell sparse matrices

2002-02-17 Thread Hal Daume III

Are there any Haskell libs for dealing with sparse matrices (or even just
libraries for writing to and reading from a standard format, say, harwell
boeing?

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

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



Re: ideas for compiler project

2002-02-17 Thread Jay Cox

On Sat, 16 Feb 2002, Dylan Thurston wrote:

 On Thu, Jan 24, 2002 at 03:38:59PM +0100, Bjorn Lisper wrote:
  I think MATLAB's matrix language provides about the right level of
  abstraction for a high-level matrix language. You can for instance write
  things like
 
  Y = inv(A)*B
 
  to assign to Y the solution of Ax = B. ...

 Just a comment on a long post...  I am personally found of MetaFont's
 approach, where you write

  Ax = B

 to find the solution to Ax = B.  When working with transformations and
 such, being able to write all your equations forwards makes it much
 easier to keep everything straight; plus, if you have several equations
 for a variable, you don't have to figure out how to gather them
 together.  Can anyone see a way to implement something like this in
 Haskell?  Or is it better to make a small interpreted language?

 Best,
   Dylan Thurston


why not write some software that does something like

let y = ((Matrix A) :*: (Vector X)) := (Matrix B))


data MatrixExp =  ...
data Sym = A | B | C  ...
data Unknown = X | Y ...
solve :: MatrixExp - Maybe (Vector Sym)
...


?


Jay Cox


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



Composition Monad

2002-02-17 Thread Andre W B Furtado

Roughly speaking, I'm in need of a monad (say MyIO) that interprets the
following code

f :: MyIO ()
f = do
action1
action2
action3
...
return ()


as applying action1 to g, then action2 to the SAME g (not the result of
action1) and so on...

Of course, this g will be specified when starting the monad (something
like runMyIO g). Does this composition monad already exist? If no, can
anyone give me some hints to create my own?

Thanks a lot
-- Andre

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



Re: Composition Monad

2002-02-17 Thread Hal Daume III

I'm not sure exactly what you mean.  Say I have something like that, then
what's the difference between saying:

f = do { action1;
 action2;
 action3 }

and simply

f = do action3

?

If the result of each of the actions is ignored for the following ones,
why do we need to do this monadically?

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Mon, 18 Feb 2002, Andre W B Furtado wrote:

 Roughly speaking, I'm in need of a monad (say MyIO) that interprets the
 following code
 
 f :: MyIO ()
 f = do
 action1
 action2
 action3
 ...
 return ()
 
 
 as applying action1 to g, then action2 to the SAME g (not the result of
 action1) and so on...
 
 Of course, this g will be specified when starting the monad (something
 like runMyIO g). Does this composition monad already exist? If no, can
 anyone give me some hints to create my own?
 
 Thanks a lot
 -- Andre
 
 ___
 Haskell mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell
 

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



Composition Monad

2002-02-17 Thread Tom Pledger

Andre W B Furtado writes:
 | Roughly speaking, I'm in need of a monad (say MyIO) that interprets the
 | following code
 | 
 | f :: MyIO ()
 | f = do
 | action1
 | action2
 | action3
 | ...
 | return ()
 | 
 | 
 | as applying action1 to g, then action2 to the SAME g (not the result of
 | action1) and so on...
 | 
 | Of course, this g will be specified when starting the monad (something
 | like runMyIO g). Does this composition monad already exist? If no, can
 | anyone give me some hints to create my own?

I think it's called a reader monad or an environment monad.  Here's a
fairly simple version:

instance Monad ((-) env) where
return x = \env - x
m = f  = \env - f (m env) env
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Composition Monad

2002-02-17 Thread Ashley Yakeley

At 2002-02-17 18:52, Tom Pledger wrote:

I think it's called a reader monad or an environment monad.  Here's a
fairly simple version:

I made one here:

http://cvs.sourceforge.net/cgi-bin/viewcvs.cgi/*checkout*/jvm-bridge/sourc
e/Haskell/ContextMonad.hs?rev=HEADcontent-type=text/plain


-- 
Ashley Yakeley, Seattle WA

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



add something to a list

2002-02-17 Thread christophe certain

Hi,

I'm a poor lonesome newbie in Haskell world, and I would like to add a string
typed on the prompt to a list of strings which is already defined.

It would look like something like :

type Path = [String]

currentPath::Path
currentPath = []

getpiece ::IO String
getpiece  =  do c -getLine
return c

putpiece:: String-Path
putpiece a = a:currentPath

and then I could combine the two functions, but obviously it doesn't work.
I dare understand that it's impossible isn't it ?

Maybe the only way is to create a new [String] each time I want to add a new 
string ? No ?

Christophe Certain
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: add something to a list

2002-02-17 Thread Adrian Hey

On Sunday 17 February 2002 08:20, christophe certain wrote:
 Hi,

 I'm a poor lonesome newbie in Haskell world, and I would like to add a
 string typed on the prompt to a list of strings which is already defined.

 It would look like something like :

 type Path = [String]

 currentPath::Path
 currentPath = []

 getpiece ::IO String
 getpiece  =  do c -getLine
   return c

 putpiece:: String-Path
 putpiece a = a:currentPath

 and then I could combine the two functions, but obviously it doesn't work.
 I dare understand that it's impossible isn't it ?

 Maybe the only way is to create a new [String] each time I want to add a
 new string ? No ?

 Christophe Certain

You seem to expect currentPath to be updated by putpiece? This won't happen
in Haskell. Once you've declared
   currentPath=[]
it will always be []. 

Values never change. If you want the functional equivalent of accumulator 
variables they have to be an argument of a recursive function. So try this..

getPath :: Path - IO Path
getPath currentPath = do
piece - getLine
if piece ==   then return currentPath
else getPath (piece:currentPath)

initialCurrentPath::Path
initialCurrentPath = []

main :: IO ()
main = do
path - getPath initialCurrentPath
putStrLn (show path)

Regards
--
Adrian Hey



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



Re: add something to a list

2002-02-17 Thread Cagdas Ozgenc



 You seem to expect currentPath to be updated by putpiece? This won't
happen
 in Haskell. Once you've declared
currentPath=[]
 it will always be [].

 Values never change. If you want the functional equivalent of accumulator
 variables they have to be an argument of a recursive function. So try
this..

 getPath :: Path - IO Path
 getPath currentPath = do
 piece - getLine
 if piece ==  then return currentPath
 else getPath (piece:currentPath)

 initialCurrentPath::Path
 initialCurrentPath = []

 main :: IO ()
 main = do
 path - getPath initialCurrentPath
 putStrLn (show path)

 Regards
 --
 Adrian Hey


Hi Adrian,

How can I add a function that sorts this list that I read from the user and
accumulate using the function that you described? I am not asking for a sort
algorithm of course, I am just wondering how to feed the IO Path as an input
to a sort function? Is it suppose to look like this:

sort :: IO Path - IO Path

or

sort :: IO Path - Path

How do you iterate over IO Path?

Thanks for taking time.

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



Re: add something to a list

2002-02-17 Thread Jay Cox

On Sun, 17 Feb 2002, Cagdas Ozgenc wrote:

 Hi Adrian,

 How can I add a function that sorts this list that I read from the user and
 accumulate using the function that you described? I am not asking for a sort
 algorithm of course, I am just wondering how to feed the IO Path as an input
 to a sort function? Is it suppose to look like this:

 sort :: IO Path - IO Path


It could.  (to make it simpler you may need a sort' :: Path - Path
function though, as in.

 sort getpath = do x - getpath  -- x has type Path
   return (sort' x)
  where sort' =   -- sort' is typed as above and produces
  -- a sorted list list of
  -- type Path


 or

 sort :: IO Path - Path

The point of the IO monad is to thread the state of the World (which
your program modifies)  explicitly through your program.  The pure
functions are the plumbing.  A function of type IO Path - Path cannot
modify the world state since the world state is not the result of function
application *.




 How do you iterate over IO Path?

Um, I cant think of another good introductory way than that sort :: IO
Path - IO Path I mentioned above.


Jay Cox



* Minus the obvious facts that haskell implementions obviously do:
   1. modify the world state as executing functions create new
  datastructures that need to be allocated, may cause garbage collection,
  maybe cause new heap allocation (do they?) or otherwise
  cause program termination (run out of stack/heap/ ... ), etc.
   2. unless it uses sort unsafeIO and/or other hacks.  unsafeIO
  generally should not be used.


PS:  Anybody got any other suggestions for IO monad entry-level docs?
 I suppose Haskell Wiki on haskell.org might be good place to allude
 to.



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



Re: add something to a list

2002-02-17 Thread Mark Carroll

On Sun, 17 Feb 2002, Jay Cox wrote:
(snip)
 PS:  Anybody got any other suggestions for IO monad entry-level docs?
(snip)

Simon's Tackling the Awkward Squad paper was a revelation for me.

-- Mark

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



Re: syntax...(strings/interpolation/here docs)

2002-02-17 Thread Carl R. Witty

Claus Reinke [EMAIL PROTECTED] writes:

 Haskell definitely supports abstraction and composition, so we can 
 factor out application aspects (not just text) that need localisation, 
 and link them (dynamically?) with the main parts of our applications. 
 Some systematic approach would be useful, but apart from keeping 
 track of the issues raised in the standards committees, I don't see 
 why Haskellers should limit themselves to the standard way of 
 patching C#/Java apps with translated text fragments.

I think there is a good reason to use standard localisation methods;
it makes it cheaper/more likely to happen.  It sounds like you're
advocating localisation methods which would require the translators to
know Haskell; this would make hiring translators more expensive (for a
commercial proposition) or significantly reduce your pool of
volunteers (if you rely on volunteer translators).

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



order of evaluation ?

2002-02-17 Thread Konst Sushenko
Title: Message



hello,

below is the 
code that i wrote as an excercise for myself (I am still learning 
haskell).

it 
implements a straighforward way to simplify boolean expressions, and should be 
self-explanatory.

my question 
is, if i have an expression such as ((Const False) :: subexp), will 
subexp be reduced first (according to the definition 
'simplify (x :: y) = simplify' ((simplify x) :: (simplify y))') 
or will laziness do the right thing, and emit (Const False) without looking into 
exp?

i think the 
latter, but would appreciate a word from an expert.

thanks
konst

PS: any 
coding suggestions, etc. are also welcome




infixr 3 ::infixr 2 :|:

data Exp = Const 
Bool | Sym 
String | Not 
Exp | Exp :: 
Exp | Exp :|: 
Exp

instance Eq Exp where 
(Const x) == (Const y) = x==y (Sym x) == (Sym 
y) = x==y (Not x) == (Not 
y) = x==y (x :: y) == (u :: v) = 
x==u  y==v || x==v  y==u (x :|: y) == 
(u :|: v) = x==u  y==v || x==v  y==u 
_ == 
_ = False

simplify (x :: y) = simplify' 
((simplify x) :: (simplify y))simplify (x :|: y) = simplify' ((simplify 
x) :|: (simplify y))simplify (Not x) = simplify' (Not (simplify 
x))simplify x = 
x

simplify' (Not (Const 
True)) = Const Falsesimplify' (Not (Const 
False)) = Const True

simplify' (Not (Not 
x)) = x

simplify' ((Not x) :: y) | x==y = 
Const Falsesimplify' (x :: (Not y)) | x==y = Const Falsesimplify' 
((Not x) :|: y) | x==y = Const Truesimplify' (x :|: (Not y)) | x==y = Const 
True

simplify' ((Const False) :: _) = 
Const Falsesimplify' (_ :: (Const False)) = Const 
Falsesimplify' ((Const True) :: x) = xsimplify' (x 
:: (Const True)) = x

simplify' ((Const True) :|: _) 
= Const Truesimplify' (_ :|: (Const True)) = Const 
Truesimplify' ((Const False) :|: x) = xsimplify' (x :|: (Const 
False)) = x

simplify' (x :: y) | 
x==y = xsimplify' (x :|: y) | 
x==y = x

simplify' 
x 
= x



re: order of evaluation ?

2002-02-17 Thread Bernard James POPE

konst writes:

 my question is, if i have an expression such as ((Const False) ::
 subexp), will subexp be reduced first (according to the definition
 'simplify (x :: y) = simplify' ((simplify x) :: (simplify y))') or
 will laziness do the right thing, and emit (Const False) without looking
 into exp?
 i think the latter, but would appreciate a word from an expert.

Hi Konst,

There is an easy way to check, try making subexp an erroneous 
computation.  There is such a value in the Prelude, it is called
undefined:

   simplify ((Const False) :: undefined)

If this bombs then you know that simplify wasn't as lazy as you thought, since
it must have tried to evaluated 'undefined'. On my version of hugs I get:

   Program error: {undefined}
 
The important bits of code are: 
 
   simplify (x :: y) = simplify' ((simplify x) :: (simplify y))
 
   simplify' (x :: (Not y)) | x==y = Const False

   simplify' ((Const False) :: _)  = Const False

The order of the equations for simplify' is important. Effectively pattern
matching causes evaluation in Haskell. To determine whether the first
equation for simplify' should be used, the second argument of :: must
be evaluated to what is called weak head normal form (whnf). This means
that the outermost constructor of that argument must be computed. 
Hence the computation with undefined fails in this case.

However, what happens if you swap the order of the equations for simplify'?
Doing so will give you the lazyness that you originally expected (for this
particular example).

Swapping the order of equations is not a silver bullet however, and you must
be very careful with how you order them.

One of the best places to learn about the operational semantics of languages
like Haskell is The Implementation of Functional Programming Languages
by Simon Peyton Jones. I think it is out of print, but you may find copies
in your local uni library if you are lucky. 

For this particular example, pay close attention to the Pattern Matching
Compiler section, which I think was done by Wadler.

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