[Haskell-cafe] Why Haskell?
Matthew Bromberg
mattcbro at earthlink.net
Sun Jul 23 01:20:06 EDT 2006
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
>
More information about the Haskell-Cafe
mailing list