foreach Re[2]: [Haskell-cafe] REALLY simple STRef examples

2006-07-22 Thread Bulat Ziganshin
Hello Bryan,

Saturday, July 22, 2006, 4:40:58 AM, you wrote:
 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]

because it looks just like for/foreach loops in imperative languages.
look at this:

import Control.Monad
import Data.IORef

infixl 0 =:, +=, -=, .=, =
ref = newIORef
val = readIORef
a=:b = writeIORef a b
a+=b = modifyIORef a (\a- a+b)
a-=b = modifyIORef a (\a- a-b)
a.=b = ((a=:).b) = val a
for :: [a] - (a - IO b) - IO ()
for = flip mapM_

newList = ref []
list = x   =  list =:: (++[x])
push list x  =  list =:: (x:)
pop list =  do x:xs-val list; list=:xs; return x

main = do
  sum - ref 0
  lasti - ref undefined
  for [1..5] $ \i - do
sum += i
lasti =: i
  sum .= (\sum- 2*sum+1)
  print = val sum
  print = val lasti

  xs - newList
  for [1..3] (push xs)
  xs = 10
  xs = 20
  print = val xs



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Why Haskell?

2006-07-22 Thread Matthew Bromberg
I am currently in the middle of a reasonably large software simulation 
of a wireless network that I'm programming
in Haskell and in C.   Progress has been slower than anticipated and I 
occasionally (probably because of looming deadlines)

ask myself did I take the right approach?

Here are the reasons why I chose Haskell initially
1)  It's mathematical elegance, I thought would lend itself to the 
complex mathematical expressions I am implementing.

2) It rates reasonably high in performance comparisons with other languages
http://shootout.alioth.debian.org/gp4sandbox/benchmark.php?test=alllang=all
3) It has a very active community who are courteous and quite helpful
4) It has an interactive shell.
5) It integrates easily with C.


The idea would be to implement hooks to some fast matrix libraries and 
some plotting routines in C and then develop the higher level logic in 
Haskell.
Since marshalling arrays and such, is a bit of a pain I structured my C 
matrix library in the form of stack based machine, using reference counting
to handle memory management and to minimize the amount of actual data I 
need to pass between C and Haskell.  This seems to work fairly well.
However I have been somewhat disabused of my original thought about how 
development would proceed.  I had hoped that I could get within a factor 
of two or so of the fast prototyping, development times of a good 
scripting language such as Matlab,  Python or Lua, but I don't think I'm 
achieving this unfortunately.


Here are some reasons why
1) Lack of debugging support.  Yes there are print statements and trace, 
but I would like to set a breakpoint.  It would be nice to do so and 
launch the GHCi interpreter with all the variable context supported.  A 
google search revealed that there is current work on this, but 
unfortunately the package is in cabal, which has spotty support in 
windows it seems.
2) Recompiling binaries (necessary in order to link in foreign object 
code into GHCi) is slow using GHC.  Moreover I have to restart GHCi if I 
want to reload a changed DLL (unless there is a way to unload a DLL in 
GHCi).  It also requires jumping around between several console windows 
to get the job done.  (I'm not using an IDE does one exist?)
3) Lack of automatic type coercion for closely related types.  In 
particular I have to use CInt and CDouble to go into and out of C.  
Unfortunately only a small subset of  library functions will actually 
support CInt so I have to explicitly coerce this values.  I usually have 
a host of compile errors initially because of this silly issue and it 
makes the code ugly.  What would help would be an automatic type 
conversion from CInt to Int and CDouble to Double.  Perhaps some warning 
level could flag these if this were 'too dangerous'.
4) GHCi is really not as useful as I'd hoped.  You can not just cut and 
paste Haskell code from a text file and run it in the interpreter.  
There is also this context issue concerning what modules are actually in 
scope.  So although in Haskell once I import a module, all of its 
functions are in scope, in GHCi, if I load this module only the exported 
functions from that module are in scope.  The result, again, is that I 
can not get an apples to apples idea of what is happening in my code. 
Thus I have been using GHCi primarily as a syntax checker for Haskell 
constructs.
5) Learning new programming patterns may have a role to play, but 
sometimes things like iteration is cleaner than recursion.  I worry 
about performance issues however.  I had to create a 50 Mbyte matrix and 
I used what I thought, initially was an elegant contruction technique in 
Haskell.  Something like this

do
...
   sequence $ [ reffill b s | s - [0..(fi temits)-1], b - [0..(fi nc)-1]]
...(push list on to matrix stack)

The refill function generates a matrix based on basestation index b and 
SU index s and pushes it on the Matrix stack in C, inside an IO monad.  
So it returns IO().
The list comprehension ends up doing a cartesian product of all (b,s) 
pairs which in this case is a large number.  fi is my shorthand for 
doing an annoying CInt to Int conversion.  The problem with this code is 
that it takes about 500 Mbytes in memory instead of 50 Mb.  Apparently 
it loads up all the potential IO actions into the huge list before 
executing it, taking the factor of 10 or so hit.  There is probably a 
nice space saving way of doing this, that executes each IO action before 
generating the next one, but I was in too much of a hurry to figure it 
out.  This also makes me wonder about the efficiency of the C 
interface.  Each IO action calls a C function  (using the unsafe 
specifier in the import declaration).  I hope there isn't too much 
overhead with this.  In my case I do almost no marshalling.  Most calls 
have no arguments and no returns, or at most require a handful of CInts 
or CDoubles. 

My application has 60-70% of it's statements in an  IO monad calling 
lots of C code.  I 

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

2006-07-22 Thread Brian Hulley

Neil Mitchell wrote:

And if someone wants to define a new and better FilePath type, I
would prefer something more abstract, such as a list of Path
components, with functions to serialize it as a String and to parse
it from a String.


A list of path components is just not enough, I'm afraid. What about
extensions? What about drives? If you want an abstract type it will
probably need to be entirely abstract, rather than with some exposed
structure.


Why not just delete Unix and Windows from the equation altogether, and 
define a simple Haskell file system with something like:


newtype Path a = Path [a]
newtype Filename a = Filename a
data Origin a -- some abstract type
  deriving Eq -- this would be nice if it is possible to implement

data IString a = FileSpecifier a = FileSpecifier !(Origin a) !(Path a) 
!(Filename a)


instance IString ByteString.Char8 ...
instance IString String ...

Origins could be created by a factory appropriate to the underlying 
operating system (they would represent drives or volumes or mount points) - 
in any case a drive can't be mentioned in a program or the program wouldn't 
be portable!


Athough even with a nice rational reconstruction the monstrously unfortunate 
fact remains that Windows is case insensitive (how impossibly moronic!!!) 
and Unix isn't so it is not possible to write code that will work the same 
for both OS's if one is required to use filenames that will look the same in 
other OS apps (ie the trick of encoding the complete Unicode char set in 
terms of legal filename chars is probably not acceptable).


Anyway this is probably straying too far from what you are trying to do at 
the moment.


Regards, Brian.

--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Why Haskell?

2006-07-22 Thread Neil Mitchell

Hi,


1) Lack of debugging support.

See Hat http://www.haskell.org/hat - it might give you the debugging
stuff you want, provided you have stuck mainly to Haskell 98.


2) Recompiling binaries (necessary in order to link in foreign object
code into GHCi) is slow using GHC.  Moreover I have to restart GHCi if I
want to reload a changed DLL (unless there is a way to unload a DLL in
GHCi).  It also requires jumping around between several console windows
to get the job done.  (I'm not using an IDE does one exist?)

Have you seen Hugs/WinHugs? Its a lot faster to load files, by a
massive factor (one particular project I use is 5 seconds in Hugs vs 8
minutes in GHC). http://haskell.org/hugs - its also much slower at
runtime :)


3) Lack of automatic type coercion for closely related types.  In
particular I have to use CInt and CDouble to go into and out of C.

You can probably play with type classes and get something doing this
automatically in some way, for some cases.


4) GHCi is really not as useful as I'd hoped.  You can not just cut and
paste Haskell code from a text file and run it in the interpreter.
There is also this context issue concerning what modules are actually in
scope.  So although in Haskell once I import a module, all of its
functions are in scope, in GHCi, if I load this module only the exported
functions from that module are in scope.

It does seem to work when I do it, not quite sure, but if you give an
exact example of what doesn't work then perhaps people can look at it.
Also :m+ is useful, in addition to :l.


Thus I have been using GHCi primarily as a syntax checker for Haskell
constructs.

If that is all you are using GHCi for, and you aren't using any GHC
specific features, Hugs will be much much quicker, and if you use
WinHugs you'll get auto-reload and hyperlinks to error locations as
well.


Thus I begin to wonder why I'm using Haskell.

If you are writing most of your code in C, then maybe you should be
using C instead of Haskell - interfacing between two languages always
has a cost.

Of course, you probably don't realise how much advantage you are
getting from Haskell. How many lines of Haskell code do you have in
this project? Think how painful that would be to code in C.

Thanks

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


Re: [Haskell-cafe] Why Haskell?

2006-07-22 Thread Spencer Janssen

On 7/22/06, Matthew Bromberg [EMAIL PROTECTED] wrote:

I used what I thought, initially was an elegant contruction technique in
Haskell.  Something like this
do
...
sequence $ [ reffill b s | s - [0..(fi temits)-1], b - [0..(fi nc)-1]]
...(push list on to matrix stack)


Try the sequence_ (note the underscore) function, it should be a big win here.


Cheers,
Spencer Janssen
___
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-22 Thread Shao Chih Kuo
Yes, largely the choice to define foreach was made to try and make it 
look more imperative, I showed it to an imperative programmer to try and 
convince him that you could program in an imperative way in Haskell if 
you really wanted to, that and I thought it'd an imperative style would 
make an interesting addition to the evolution of a Haskell programmer.


Bulat Ziganshin wrote:

Hello Bryan,

Saturday, July 22, 2006, 4:40:58 AM, you wrote:
  

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]
  


because it looks just like for/foreach loops in imperative languages.
look at this:

import Control.Monad
import Data.IORef

infixl 0 =:, +=, -=, .=, =
ref = newIORef
val = readIORef
a=:b = writeIORef a b
a+=b = modifyIORef a (\a- a+b)
a-=b = modifyIORef a (\a- a-b)
a.=b = ((a=:).b) = val a
for :: [a] - (a - IO b) - IO ()
for = flip mapM_

newList = ref []
list = x   =  list =:: (++[x])
push list x  =  list =:: (x:)
pop list =  do x:xs-val list; list=:xs; return x

main = do
  sum - ref 0
  lasti - ref undefined
  for [1..5] $ \i - do
sum += i
lasti =: i
  sum .= (\sum- 2*sum+1)
  print = val sum
  print = val lasti

  xs - newList
  for [1..3] (push xs)
  xs = 10
  xs = 20
  print = val xs



  


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


Re: [Haskell-cafe] Why Haskell?

2006-07-22 Thread Matthew Bromberg

1) Hat looks really interesting thanks.  Hopefully it will run on windows.

2) I have downloaded the latest version of WinHugs.  In the end I need 
my Haskell to compile under GHC for performance reasons.   I am 
concerned about portability, especially as concerns the ffi.  I got 
scared off by the need for a separate compilation to support it.  
Perhaps it wouldn't be so bad after I get used to it or try to configure 
a script or something to make it easier.  I might give it a try after my 
current deadlines.


3)  The problem here is existing code.  I don't want to add every 
function that I use into a class just to maintain simple polymorphism 
over closely related numeric types.  This would take longer than just 
calling the coercion routines.  It's funny how trivial stuff likes this 
gets irritating when you are writing a lot of code.  Maybe I'm just in a 
bad mood or something.


4)  Hmm, a simple example I tried actually worked, however I have a file 
that has this header

module Parsefile where
import System.IO
import System.IO.Unsafe
import Text.ParserCombinators.Parsec
import Data.HashTable
...

For some reason it requires that I use the fully qualified name 
Data.HashTable.lookup instead of just lookup to get the correct 
functionality.


I think I understand my issue now with this (other than the anomaly of 
the above example).  I've been using the make option with ghc to compile 
all the dependent sources, creating binaries for all of them.  Those 
binaries can be loaded into GHCi, but if you do so it will not make the 
imports available to you for use.  Thus my main.hs has the header

import Matrix
import Parsefile
import Array
import NetPrams
import System.IO.Unsafe

.

If main.hs has not been brought up to date, I can load main.hs into the 
interpreter and the functions defined in Matrix for example will be in 
scope and usable.  If on the other hand I've just run ghc on main, I can 
load main.hs in, but the functions in Matrix will not be available.  
Perhaps the solution is to create a script file that loads all the 
modules in and adds them to the current scope.



I do want to understand the advantages of Haskell.  My approach has been 
to consign the heavy imperative, state manipulating code to C and leave 
the higher end stuff to Haskell.  The nature of my problem  (a 
simulation) necessitates holding state for efficiency reasons.  (e.g. I 
don't want to copy a 500 MB matrix every time I change an entry.)  I 
assumed that Haskell would be easier to write and perhaps maintain than 
the horrors of pure C.  At this point there is no turning back. I will 
probably answer this question soon enough.








Neil Mitchell wrote:

Hi,


1) Lack of debugging support.

See Hat http://www.haskell.org/hat - it might give you the debugging
stuff you want, provided you have stuck mainly to Haskell 98.


2) Recompiling binaries (necessary in order to link in foreign object
code into GHCi) is slow using GHC.  Moreover I have to restart GHCi if I
want to reload a changed DLL (unless there is a way to unload a DLL in
GHCi).  It also requires jumping around between several console windows
to get the job done.  (I'm not using an IDE does one exist?)

Have you seen Hugs/WinHugs? Its a lot faster to load files, by a
massive factor (one particular project I use is 5 seconds in Hugs vs 8
minutes in GHC). http://haskell.org/hugs - its also much slower at
runtime :)


3) Lack of automatic type coercion for closely related types.  In
particular I have to use CInt and CDouble to go into and out of C.

You can probably play with type classes and get something doing this
automatically in some way, for some cases.


4) GHCi is really not as useful as I'd hoped.  You can not just cut and
paste Haskell code from a text file and run it in the interpreter.
There is also this context issue concerning what modules are actually in
scope.  So although in Haskell once I import a module, all of its
functions are in scope, in GHCi, if I load this module only the exported
functions from that module are in scope.

It does seem to work when I do it, not quite sure, but if you give an
exact example of what doesn't work then perhaps people can look at it.
Also :m+ is useful, in addition to :l.


Thus I have been using GHCi primarily as a syntax checker for Haskell
constructs.

If that is all you are using GHCi for, and you aren't using any GHC
specific features, Hugs will be much much quicker, and if you use
WinHugs you'll get auto-reload and hyperlinks to error locations as
well.


Thus I begin to wonder why I'm using Haskell.

If you are writing most of your code in C, then maybe you should be
using C instead of Haskell - interfacing between two languages always
has a cost.

Of course, you probably don't realise how much advantage you are
getting from Haskell. How many lines of Haskell code do you have in
this project? Think how painful that would be to code in C.

Thanks

Neil



Re: [Haskell-cafe] Why Haskell?

2006-07-22 Thread Bertram Felgenhauer
Matthew Bromberg wrote:
 4)  Hmm, a simple example I tried actually worked, however I have a file 
 that has this header
 module Parsefile where
 import System.IO
 import System.IO.Unsafe
 import Text.ParserCombinators.Parsec
 import Data.HashTable
 ...
 
 For some reason it requires that I use the fully qualified name 
 Data.HashTable.lookup instead of just lookup to get the correct 
 functionality.

The reason is that the standard Prelude also provides function
called 'lookup'. [*] You could hide it by explicitely importing the
Prelude:

  import Prelude hiding (lookup)

Another solution is to import the HashTable module with a shorter
name to save typing (and avoid noise) in the Code:

  import Data.HashTable as H

allows you to use H.lookup for the lookup. If you make the import
qualified,

  import qualified Data.HashTable as H

you are forced to use that prefix, but you can use the Prelude's
lookup without any prefix again.

By specifying the names to import you can create any mix of
prefixed and non-prefixed functions you want. Another useful
thing to know is that you can import different modules with the
same name (beware of conflicting symbols though). For example,
adding

  import Data.HashTable (HashTable)

to the qualified import allows you to use the type 'HashTable'
without the 'H.' prefix.

regards,

Bertram

[*] it'd be nice if the name resolution could be guided by the
type checker - but that's probably hard. Has anyone tried that?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe