Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread SevenThunders


Jared Updike wrote:
> 
> GSL Haskell bindings:
> 
> http://dis.um.es/~alberto/GSLHaskell/
> http://dis.um.es/~alberto/GSLHaskell/doc/
> 
> Specifically for Linary Algebra:
> http://dis.um.es/~alberto/GSLHaskell/doc/GSL-Base.html
> 
>> > You make a good point and the decision was by no means cut and dry. 
>> However
>> > I made a point of developing some test code using some the newer array
>> data
>> > types and looked at maintaining the array in Haskell and then directly
>> > calling Blas etc.  I even had a nice polymorphic matrix class going.
>> > However I found the array interface just a bit too 'clunky' to use a
>> > technical term.  The withArray interface is not very appealing.  The
>> layers
>> > of lambda notation was giving me a headache.
> 
> I think part of the problem here is not necessarily C or Haskell's
> fault, but rather that what you were trying to do was write a library
> (or needed the right library). Library writing is hard enough on its
> own, much less when one is relatively new to Haskell! Hopefully you
> will find the right tool for the job and things will go well!
> 
>   Jared.
> -- 
> http://www.updike.org/~jared/
> reverse ")-:"
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

I looked at that.  It would have been nice to use it however it seems to
have issues on Windows.  Although my windows requirement probably could have
been relaxed, at the beginning of the project our network was entirely
windows based.


-- 
View this message in context: 
http://www.nabble.com/Why-Haskell--tf1986013.html#a5460683
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Jared Updike

GSL Haskell bindings:

http://dis.um.es/~alberto/GSLHaskell/
http://dis.um.es/~alberto/GSLHaskell/doc/

Specifically for Linary Algebra:
http://dis.um.es/~alberto/GSLHaskell/doc/GSL-Base.html


> You make a good point and the decision was by no means cut and dry.  However
> I made a point of developing some test code using some the newer array data
> types and looked at maintaining the array in Haskell and then directly
> calling Blas etc.  I even had a nice polymorphic matrix class going.
> However I found the array interface just a bit too 'clunky' to use a
> technical term.  The withArray interface is not very appealing.  The layers
> of lambda notation was giving me a headache.


I think part of the problem here is not necessarily C or Haskell's
fault, but rather that what you were trying to do was write a library
(or needed the right library). Library writing is hard enough on its
own, much less when one is relatively new to Haskell! Hopefully you
will find the right tool for the job and things will go well!

 Jared.
--
http://www.updike.org/~jared/
reverse ")-:"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Jason Dagit

You make a good point and the decision was by no means cut and dry.  However
I made a point of developing some test code using some the newer array data
types and looked at maintaining the array in Haskell and then directly
calling Blas etc.  I even had a nice polymorphic matrix class going.
However I found the array interface just a bit too 'clunky' to use a
technical term.  The withArray interface is not very appealing.  The layers
of lambda notation was giving me a headache.

The idea of separating the imperative code into an imperative language was
appealing to me.  Moreover using a stack based architecture for matrix
operations makes the C end of things very easy to implement.  The big
bugaboo of memory management issues pretty much disappears, and thinking of
the world state in the IO monad as a stack of matrices has a nice intuitive
appeal for me.  It seems to work well so far as I said earlier.  I'm not
sure all my issues would have gone away if I had tried to do more of the
matrix op.s in Haskell.  It is pretty much a given that I need to interface
to external optimized libraries, that's where the big number crunching is
occuring and those libraries have had teams of Ph.D.s working on them for
years.  I want to leverage that.  My approach actually minimizes the amount
of marshalling I have to do between C and Haskell.   The stack manipulations
are simply scripted in a do clause, with nary an argument being passed.



Has any one created binding for the numarray library ala Python
Numarray?  I've heard it's a very good and fast array interface.
Perhaps it would be useful for this sort of task.

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread SevenThunders


David F. Place wrote:
> 
> 
> On Jul 23, 2006, at 1:20 AM, Matthew Bromberg wrote:
> 
>> 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.
>>
> 
> Hi Matthew,
> 
> It seems that a lot of your issues stem from the design decision to  
> implement a good chunk of your program in C.   There are certainly  
> ways to implement an indexed data-structure in Haskell with good  
> performance for persistent functional updates.  Alternatively, you  
> could write imperative code in Haskell to update the array in place  
> non-persistently.  So, the decision not to use Haskell for that part  
> may be a case of premature optimization.
> 
> Cheers, David
> 
> 
> David F. Place
> mailto:[EMAIL PROTECTED]
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

You make a good point and the decision was by no means cut and dry.  However
I made a point of developing some test code using some the newer array data
types and looked at maintaining the array in Haskell and then directly
calling Blas etc.  I even had a nice polymorphic matrix class going. 
However I found the array interface just a bit too 'clunky' to use a
technical term.  The withArray interface is not very appealing.  The layers
of lambda notation was giving me a headache.  

The idea of separating the imperative code into an imperative language was
appealing to me.  Moreover using a stack based architecture for matrix
operations makes the C end of things very easy to implement.  The big
bugaboo of memory management issues pretty much disappears, and thinking of
the world state in the IO monad as a stack of matrices has a nice intuitive
appeal for me.  It seems to work well so far as I said earlier.  I'm not
sure all my issues would have gone away if I had tried to do more of the
matrix op.s in Haskell.  It is pretty much a given that I need to interface
to external optimized libraries, that's where the big number crunching is
occuring and those libraries have had teams of Ph.D.s working on them for
years.  I want to leverage that.  My approach actually minimizes the amount
of marshalling I have to do between C and Haskell.   The stack manipulations
are simply scripted in a do clause, with nary an argument being passed.
-- 
View this message in context: 
http://www.nabble.com/Why-Haskell--tf1986013.html#a5458965
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Re[2]: Why Haskell?

2006-07-23 Thread SevenThunders


Bulat Ziganshin-2 wrote:
> 
> Hello Matthew,
> 
> Sunday, July 23, 2006, 10:35:41 AM, you wrote:
> 
>  >> sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
>> nc)-1]]
> 
>> Now thats interesting.  I can see that this function is more appropriate
>> since I do not need to retrieve data from the IO monad,
>> but what I don't understand is why it's actually faster.  I will give it
>> a try and test it on a large set to see if things change.
> 
> let's see at their (possible) definitions:
> 
> sequence [] = return []
> sequence (action:actions) = do x <- action
>xs <- sequence actions
>return (x:xs)
>
> sequence_ [] = return ()
> sequence_ (action:actions) = do action
> sequence_ actions
> 
> sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the
> result is what just all the action in list are sequentially performed
> without creating any intermediate data structures. so, using sequence_
> in above example is equivalent to implementing this cycle by hand.
> 
> but when you use sequence, result of each action is saved and list
> of all results is built. this list requires 12 bytes per element, so
> you got 600 mb of garbage and much slower execution
> 
> 
> Thanks Bulat, that was concise and explains it well.  Now the question is
> what do I do if I do have data building up in the monad.  ie if I want to
> generate a large list of doubles in the IO monad? Moreover those doubles
> depend in some way on data wrapped up or generated in the monad. It seems
> that building a list of IO actions in advance is a bad idea.  
> 
> Perhaps the implementaton with the tail call will work in this case if an
> extra accumulator argument is added.
> 
> -- 
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
-- 
View this message in context: 
http://www.nabble.com/Why-Haskell--tf1986013.html#a5458595
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Matthew Bromberg
I agree that this would be the cleaner solution.  In fact I already 
have a typedef for the Double type in anticipation of using different 
sized floating point.
Unfortunately I rely heavily on the BLAS linear algebra libraries.  As 
long as I can type cast the haskell types in C to double or int where 
appropriate, I'm OK, at the expense of making some global changes to the 
code.  Fortunately all my Blas interfaces are performed through 
typedefs.  I'll have to look into this.


Thanks again for the tip. 

Given that I'm making a lot of C calls through Haskell, with the unsafe 
tag in the import statement,  does anyone have an idea of what kind of 
overhead I might still be incurring?  I'm assuming that it's fairly 
minimal.  The one call that has to be safe has a callback to a numerical 
Haskell function that is called repeatedly over every element in a 
potentially large matrix.  I am also concerned about the performance of 
that procedure.


Brian Hulley wrote:

Matthew Bromberg wrote:

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.


It would be better to just use the Haskell numeric types in the first 
place ie replace all CInt, CDouble etc by Int, Double etc and change 
your C code accordingly to use HsInt, HsDouble instead of plain int, 
double etc. Hopefully this should just be a trivial matter of changing 
a few typedefs in a C header as long as the C functions don't refer to 
'int' 'double' etc directly.


Regards, Brian.


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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Thiago Arrais

Matthew,

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

I'm not using an IDE does one exist?


You may want to use EclipseFP for your Haskell work. It is still a
work in progress, but it may be worth to give it a try.

http://eclipsefp.sourceforge.net

Cheers,

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


Re: Re[2]: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Pepe Iborra

Bulat,  now that Krasimir has resumed work on Visual Haskell, I have
planned to pursue an integration of the ghc-api debugger with Visual
Haskell as soon as possible.
But as we get closer to having dynamic breakpoints working 100%, the
plain ghci debugging support starts to look as a fairly nice addition
to anyone's ghc toolkit.
Of course, I agree with you that it's too early to recommend it for real work.

On 23/07/06, Bulat Ziganshin <[EMAIL PROTECTED]> wrote:

Hello Pepe,

Sunday, July 23, 2006, 5:23:18 PM, you wrote:

>> 1) Lack of debugging support.  Yes there are print statements and trace,

> You can find more info about this project in the Haskell wiki at:
>  http://haskell.org/haskellwiki/Ghci/Debugger

> All you'd need to do is to compile ghc-6.5 with a few patches (if you
> are in Windows you can use MinGW). But I am afraid you are right, this
> is a work in progress and we are in the process of polishing some
> serious issues right now. I can't really recommend it for now.

is this will be really usable without gui support? your project is
really great, but i think it's too early to recommend it for real work
(as opposite to hacking/integration with IDEs)


--
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



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


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

2006-07-23 Thread Bulat Ziganshin
Hello Brian,

Sunday, July 23, 2006, 5:31:35 PM, you wrote:

>>> instance IString ByteString.Char8 ...
>>> instance IString String ...
>> class ListLike ce e | ce->e

> class ISeq seq_a a | seq_a -> a where -- (*)

there is also Collection library:
darcs get --partial http://darcs.haskell.org/packages/collections/

it contains many classes, including:

-- | Class of sequential-access types.
-- In addition of the 'Collection' services, it provides deconstruction and 
concatenation.
class (Monoid c, Collection c a a) => Sequence c a where
-- | The first @i@ elements of a sequence.
take :: Int -> c -> c
-- | Elements of a sequence after the first @[EMAIL PROTECTED]
drop :: Int -> c -> c
-- | Split a sequence at a given index.
splitAt :: Int -> c -> (c,c)
-- | Reverse a sequence.
reverse :: c -> c
-- | Analyse the left end of a sequence.
front :: Monad m => c -> m (a,c)
-- | Analyse the right end of a sequence.
back :: Monad m => c -> m (c,a)
-- | Add an element to the left end of a sequence.
cons :: a -> c -> c
-- | Add an element to the right end of a sequence.
snoc :: c -> a -> c
-- | The 'isPrefix' function takes two seqences and returns True iff 
-- the first is a prefix of the second.
isPrefix :: Eq a => c -> c -> Bool


but this class is not ideal for integration with ByteString library
which implements many custom algorithms which (i suppose) use details
of ByteString implementation. so, something like

class (Sequence c a) => ListLike c a where
  split, splitBy

would be useful. and then we should integrate your idea:

>  class IChar c where
>  class (IChar c, ISeq s c) => IString s where

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Bulat Ziganshin
Hello Pepe,

Sunday, July 23, 2006, 5:23:18 PM, you wrote:

>> 1) Lack of debugging support.  Yes there are print statements and trace,

> You can find more info about this project in the Haskell wiki at:
>  http://haskell.org/haskellwiki/Ghci/Debugger

> All you'd need to do is to compile ghc-6.5 with a few patches (if you
> are in Windows you can use MinGW). But I am afraid you are right, this
> is a work in progress and we are in the process of polishing some
> serious issues right now. I can't really recommend it for now.

is this will be really usable without gui support? your project is
really great, but i think it's too early to recommend it for real work
(as opposite to hacking/integration with IDEs)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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

2006-07-23 Thread Brian Hulley

Bulat Ziganshin wrote:

Hello Brian,

Sunday, July 23, 2006, 1:20:36 AM, you wrote:


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


i think that we should ask Donald Stewart who is patronized SoC
project involving development of such type class. If he will say that
such type class is not developed, i feel himself enough interested to
start developing such class. i can add this module to ByteString lib,
if there is no better variants

i propose something like this:

class ListLike ce e | ce->e
instance ListLike [a] a
instance ListLike Data.ByteString.ByteString Word8
instance ListLike Data.ByteString.Lazy.ByteString Word8
instance ListLike Data.ByteString.Char8.ByteString Char
instance ListLike Data.ByteString.Lazy.Char8.ByteString Char


Hi Bulat -

I've been thinking of a sequence class for the project I'm working on at the 
moment, something like:


   class ISeq seq_a a | seq_a -> a where -- (*)
   empty :: seq_a
   single :: a -> seq_a
   length :: seq_a -> Int
   append :: seq_a -> seq_a -> seq_a

   pushL :: a -> seq_a -> seq_a  -- (**)
   pushR :: seq_a -> a -> seq_a

   at :: seq_a -> Int -> a
   atL :: seq_a -> a-- (***)
   atR :: seq_a -> a

   viewL :: seq_a -> ViewL
   -- plus lots of other ops

   toList :: seq_a -> [a]
   fromList :: [a] -> seq_a

   data ViewL seq_a a = EmptyL | PushL !a !seq_a
   -- this is strict so we don't pay an extra laziness penalty

(meaningful names such as pushL, pushR etc inspired by the absolutely 
brilliant C++ STL library as opposed to odd lispy names like cons and snoc 
(do we really want to have to start reading lexemes backwards then apply a 
quirky historical reference to understand code?)) then the IString class 
would be something like:


class IChar c where
toCChar :: c -> CChar
fromCChar :: CChar -> c

class (IChar c, ISeq s c) => IString s where
   withCString :: MonadIO m => s -> (Ptr CChar -> IO a) -> m a
   withCStringLen :: MonadIO m => s -> (Ptr CChar -> Int -> IO a) -> m 
a


   withCAString :: MonadIO m => s -> (Ptr CChar -> IO a) -> m a
   withCAStringLen :: MonadIO m => s -> (Ptr CChar -> Int -> IO a) -> m 
a


   -- possibly also withCWString etc

   peekCString :: Ptr CChar -> s
   peekCAString :: Ptr CChar -> s

ie the IString class deals with the complexity of marshalling character 
strings which may or may not be in Unicode.


(*) I assume that the reason for putting the collection type first is 
because usually you want to map a collection of elements to a collection of 
some different element type rather than mapping between different collection 
types.


(**) I think conventional names like "foldr" should be replaced by "foldR" 
so that camel case is followed consistently and so that confusing names like 
"reducer", which is a word by itself in English, cannot arise when "reduceR" 
was meant.


(***) "atL" and "atR" are more visual than the conventional names "head" and 
"last". I think names should be chosen so that the syntactic differences 
between lexemes indicate similarity of meaning, thus it's clear that "atL" 
"atR" and "at" all do something similar, whereas "head", "last", and 
"index" are just 3 random English words whose perceived commonality depends 
on many years programming experience and is therefore vague and loose.


Anyway - it's just a rough idea 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-23 Thread Pepe Iborra

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.


You can find more info about this project in the Haskell wiki at:
http://haskell.org/haskellwiki/Ghci/Debugger

All you'd need to do is to compile ghc-6.5 with a few patches (if you
are in Windows you can use MinGW). But I am afraid you are right, this
is a work in progress and we are in the process of polishing some
serious issues right now. I can't really recommend it for now.

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


Re: Re[2]: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Neil Mitchell

Hi,


sequence [] = return []
sequence (action:actions) = do x <- action
   xs <- sequence actions
   return (x:xs)

sequence_ [] = return ()
sequence_ (action:actions) = do action
sequence_ actions


So, by appending an underscore at the end of a name, you massively
improve the runtime behaviour of the program. That to me sounds like a
hack :)

Would it not be possible to add a GHC rule like the following:

forall a b . sequence a >> b  = sequence_ a >> b

I'm not sure if thats correct, a valid rule definition, or semantics
preserving, but if it was it would be nice :)

Thanks

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


Re[2]: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Bulat Ziganshin
Hello Matthew,

Sunday, July 23, 2006, 10:35:41 AM, you wrote:

 >> sequence $ [ reffill b s | s <- [0..(fi temits)-1], b <- [0..(fi
> nc)-1]]

> Now thats interesting.  I can see that this function is more appropriate
> since I do not need to retrieve data from the IO monad,
> but what I don't understand is why it's actually faster.  I will give it
> a try and test it on a large set to see if things change.

let's see at their (possible) definitions:

sequence [] = return []
sequence (action:actions) = do x <- action
   xs <- sequence actions
   return (x:xs)
   
sequence_ [] = return ()
sequence_ (action:actions) = do action
sequence_ actions

sequence_ is TAIL-RECURSIVE function. moreover, when it's inlined, the
result is what just all the action in list are sequentially performed
without creating any intermediate data structures. so, using sequence_
in above example is equivalent to implementing this cycle by hand.

but when you use sequence, result of each action is saved and list
of all results is built. this list requires 12 bytes per element, so
you got 600 mb of garbage and much slower execution



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread David F. Place


On Jul 23, 2006, at 1:20 AM, Matthew Bromberg wrote:

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.




Hi Matthew,

It seems that a lot of your issues stem from the design decision to  
implement a good chunk of your program in C.   There are certainly  
ways to implement an indexed data-structure in Haskell with good  
performance for persistent functional updates.  Alternatively, you  
could write imperative code in Haskell to update the array in place  
non-persistently.  So, the decision not to use Haskell for that part  
may be a case of premature optimization.


Cheers, David


David F. Place
mailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Brian Hulley

Matthew Bromberg wrote:

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.


It would be better to just use the Haskell numeric types in the first place 
ie replace all CInt, CDouble etc by Int, Double etc and change your C code 
accordingly to use HsInt, HsDouble instead of plain int, double etc. 
Hopefully this should just be a trivial matter of changing a few typedefs in 
a C header as long as the C functions don't refer to 'int' 'double' etc 
directly.


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[2]: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-23 Thread Bulat Ziganshin
Hello Brian,

Sunday, July 23, 2006, 1:20:36 AM, you wrote:

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

i think that we should ask Donald Stewart who is patronized SoC
project involving development of such type class. If he will say that
such type class is not developed, i feel himself enough interested to
start developing such class. i can add this module to ByteString lib,
if there is no better variants

i propose something like this:

class ListLike ce e | ce->e
instance ListLike [a] a
instance ListLike Data.ByteString.ByteString Word8
instance ListLike Data.ByteString.Lazy.ByteString Word8
instance ListLike Data.ByteString.Char8.ByteString Char
instance ListLike Data.ByteString.Lazy.Char8.ByteString Char



-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Neil Mitchell

Hi


> 1) Hat looks really interesting thanks.  Hopefully it will run on windows.
Under mingw or cygwin, possibly.  Natively, not.


http://www.haskell.org//pipermail/hat/2006-July/000288.html - I ported
Hat to Windows natively last week. No mingw or cygwin required.

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-23 Thread Malcolm Wallace
Matthew Bromberg <[EMAIL PROTECTED]> writes:

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

Under mingw or cygwin, possibly.  Natively, not.

> 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.

Possibly you just need to move the coercions to a single more manageable
location.  e.g. you could rename the FFI calls, then wrap them with a
simple coercion function, and call it by the original name.

   inject :: CInt -> Int
   eject  :: Int  -> CInt

   foreign import ccall "blah" prim_blah :: CInt -> CInt
   blah x = inject (prim_blah (eject x))

By the way, there are tools for generating FFI bindings that can create
code like this (e.g. GreenCard).

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


Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Chris Kuklewicz

Matthew Bromberg 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



Now thats interesting.  I can see that this function is more appropriate 
since I do not need to retrieve data from the IO monad,
but what I don't understand is why it's actually faster.  I will give it 
a try and test it on a large set to see if things change.

Thanks for the tip.


The best way I have to explain is to pedantically go through how I would try to 
understand why it is faster.  I hope this is something useful in this message, 
and nothing that is taken as condescending.


Thinking about memory usage and garbage collection in strict language like Java 
is tricky, and thinking about them in non-strict Haskell is another layer of 
consideration. ( But in this case it will be quite easy to understand from the 
code.)  I will look at the code:


1. See that sequence and sequence_ are exposed by Prelude
2. Since that is part of the Haskell 98 definition, google a copy of the 
"Haskell 98 report" at http://www.haskell.org/onlinereport/
3. Look at "8. Standard Prelude" at 
http://www.haskell.org/onlinereport/standard-prelude.html

4. Scroll down to sequence and sequence_ to see:

sequence   :: Monad m => [m a] -> m [a] 
sequence   =  foldr mcons (return [])

where mcons p q = p >>= \x -> q >>= \y -> return (x:y)


sequence_  :: Monad m => [m a] -> m () 
sequence_  =  foldr (>>) (return ())


A more generally useful way to look up the actual ghc source code is:

1. In ghci do ":i sequence" to see it comes from Control.Monad
2. look at http://www.haskell.org/ghc/docs/latest/html/libraries/index.html
3. See "Control.Monad" is in the "base" packagage
4. Browse through http://haskell.org/ghc/ to "Developers(Wiki)" and "Getting the 
Sources" to http://hackage.haskell.org/trac/ghc/wiki/GhcDarcs

5. Follow the link to package "base" via http://darcs.haskell.org/packages/base/
6. Browse to "Control" and "Monad.hs" to 
http://darcs.haskell.org/packages/base/Control/Monad.hs

7. Scroll down to sequence and sequence_ to see:


-- | Evaluate each action in the sequence from left to right,
-- and collect the results.
sequence   :: Monad m => [m a] -> m [a] 
{-# INLINE sequence #-}

sequence ms = foldr k (return []) ms
where
  k m m' = do { x <- m; xs <- m'; return (x:xs) }

-- | Evaluate each action in the sequence from left to right,
-- and ignore the results.
sequence_:: Monad m => [m a] -> m () 
{-# INLINE sequence_ #-}

sequence_ ms =  foldr (>>) (return ()) ms


The implementation code is only 1 or 2 lines, and reveals it is just really 
useful shorthand for a right fold.


Right folds are notorious for being bad memory consumers when they are strict in 
the second argument of their accumulation function.  And indeed this is the 
problem in this case.


Looking at sequence_ first, since it is simpler:  It essentially says to put 
(>>) between all the elements of the list of IO actions which is equivalent to 
putting the actions one after another in "do" notation.  It never needs to 
remember the result of any of the actions, so the garbage collector will 
occasionally run and destroy the intermediate results.  Those intermediate 
results may pile up in memory as dead references, so the gc might clean them 
only after they (or something else) cause memory pressure.


Now look at sequence, and remember that the Monad m here is Monad IO.  The IO 
monad runs in a strict manner.  Consider " do { x <- m; xs <- m'; return (x:xs) 
}" which could have been written


sequence ms = foldr k (return []) ms
  where
k m m' = do
  x <- m
  xs <- m'
  return (x:xs)

sequence [a,b,c] = foldr k (return []) [a,b,c]

can be expanded via the foldr definition and some syntactic sugar as

a `k` (b `k` (c `k` return []))

can be expanded via the `k` definition and some syntactic sugar as

do
  x <- a
  xs <- (b `k` (c `k` return []))
  return (x:xs)

So you can see the return value of a is x.  Then it goes and computes the rest 
of the sequence for b and c while holding onto the reference for x.  The "return 
(x:xs)" line is later and also refers to x, which means x is live instead of 
dead, so the garbage collector will not remove it.


The same analysis applies to the values returned by b and c.  All the 
intermediate values are live until the first `k` executes the "return" statement 
with all the values.  This is why the memory usage is maximal.


The problem was created by the IO Monad evaluating the b and c strictly once "xs 
<- (b `k` (c `k` return []))" was encountered.  The use of sequence with a 
different Monad which was lazy instead would have different evaluati