SevenThunders wrote:
>
>
>
> The new behavior is that under certain conditions a certain matrix inner
> product produces undefined floats, that should not be there.
>
I now have a simple example that I have posted as ticket number 1944 for ghc
6.8.1. The behavior is th
Ian Lynagh wrote:
>
>
> Can any of you give us a testcase for this, please?
>
>
> Thanks
> Ian
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
I started to work on this b
Simon Peyton-Jones wrote:
>
> Alberto, SevenThunders, Joel,
>
> Glark. This is not good. Thank you for being so polite about it. And
> thanks for working on a reproducible test case -- without that we are 100%
> stuck.
>
> We did fix one just-possibly-related bu
The good news is that my code compiles without error and much faster under
ghc 6.8.1.
The bad news is that there appear to be subtle bugs that did not occur when
I compiled things under
6.6.1. One issue is that my code is somewhat complex and links into a C
library as well.
The new behavior is
Alberto Ruiz-2 wrote:
>
>
> Hmm, I' sorry... all seems to work well for me if I set -O -fvia-C for
> building the library and for final program compilation. But I will also
> try
> to find a minimum test case. In the meantime I have sent to Ian
> information
> to expose the problem with my
Alberto Ruiz-2 wrote:
>
> Hello,
>
> I have had exactly the same problem with my bindings to GSL, BLAS and
> LAPACK.
> The foreign functions (!) randomly (but very frequently) produced NaN with
> ghc-6.8.1 -O. As usual, I first thought that I had a subtle bug related to
> the foreign pointe
Al Falloon wrote:
>
> SevenThunders wrote:
>> Well it certainly requires some thought here. As I see it, I now have
>> two
>> reasonable choices. Either I pull all my matrix operations back inside
>> the
>> IO monad and avoid the matrix action as a matrix
Paul Johnson-2 wrote:
>
> SevenThunders wrote:
>> Unfortunately if I wrap my matrix references in the IO monad, then at
>> best
>> computations like
>> S = A + B are themselves IO computations and thus whenever they are
>> 'invoked' the co
Ronald Guida wrote:
>
>
>
>
> I could translate your example to the following:
>
>> let S = A += B in
>> do
>> s <- S
>> (r,c) <- size (return s)
>> k <- matindex (return s)
>
> This should only perform action S one time.
>
That's a good point actually. If I am caref
apfelmus wrote:
>
> SevenThunders wrote:
>> Ryan Ingram wrote:
>>> As long as the FFI calls don't make destructive updates to existing
>>> matrices, you can do what you want.
>>>
>>> For example, assuming you have:
>>>
>
Dominic Steinitz wrote:
>
>> If you arrange the types to try to do all the operations inside the IO
>> monad you can't chain together more than 1 binary operation. eg.
>>
>> do
>>S <- A + B
>>Z <- Q * S
>>
>> vs
>>
>> do
>>S <- Q * (A + B)
>>
>> Are there any suggestions for
Ryan Ingram wrote:
>
> As long as the FFI calls don't make destructive updates to existing
> matrices, you can do what you want.
>
> For example, assuming you have:
>
> -- adds the second matrix to the first & overwrites the first
> matrixAddIO :: MatrixIO -> MatrixIO -> IO ()
>
> -- creates
I have a matrix library written in C and interfaced into Haskell with a lot
of additional Haskell
support. The C library of course has a lot of side effects and actually
ties into the BLAS libraries, thus at the present time, most of the
interesting calls are done in the IO monad. I have no inte
Did I find a bug cabal?
I have attempted to fix the problem
Main.c:(.text+0x22): undefined reference to `__stginit_ZCMain'
by compiling my Haskell library using the flag -no-hs-main. One would think
that this would make sense if the library is to be used by an external C
program. However I am
SevenThunders wrote:
>
> I have a large Haskell/C project that needs to be linked against an even
> larger set of C libraries and object files (OpNet) on a linux box (Fedora
> Core 7). So far I have been able to link my Haskell libraries to some C
> test code containing
I have a large Haskell/C project that needs to be linked against an even
larger set of C libraries and object files (OpNet) on a linux box (Fedora
Core 7). So far I have been able to link my Haskell libraries to some C
test code containing a main function without incident. However the link
flag
Bulat Ziganshin-2 wrote:
>
> Hello SevenThunders,
>
> Saturday, June 30, 2007, 7:45:57 AM, you wrote:
>
>> My own code is half Haskell and half C. My build process is rather
>> complex
>
> i have the same. initially C code was compiled by gcc but
SevenThunders wrote:
>
> perhaps what's contained in foo.hi that informs ghc what names to actually
> link to.
>
>
I'm not so sure if this is correct or not. The truth is I have no .hi files
in the directory I try to link my test code, and yet it's somehow fin
I have a very complex project that has to play nice with a lot of C code
written by other people.
My own code is half Haskell and half C. My build process is rather complex
since I generate about 5 different libraries, some of them export Haskell
routines. A supreme effort was made to try to mak
I discovered a curious thing after a compiling a medium sized Haskell project
using
the 64 bit linux Haskell GHC 6.6.1 compiler. Several of the generated
object files (.o) show up
as containing the virus Downloader.Obfuskated by my AVG anti-virus program
when viewing
the files from windows xp 64.
Brandon S. Allbery KF8NH wrote:
>
>
> On May 5, 2007, at 0:21 , SevenThunders wrote:
>> Is there a simple way to detect what operating system a given
>> Haskell program
>> is running und
Is there a simple way to detect what operating system a given Haskell program
is running under?
It would help to make some programs that might have to interact with the
operating system more portable.
I haven't been able to quite figure out a simple way to do this.
--
View this message in cont
Dan Weston wrote:
>
> In the GHC docs:
> http://www.haskell.org/ghc/docs/6.4.1/html/users_guide/sec-ffi-ghc.html#using-own-main
>
> "There can be multiple calls to hs_init(), but each one should be
> matched by one (and only one) call to hs_exit()[8]."
>
> What exactly happens with nested ca
jasonm wrote:
>
> While we're on the topic, does anyone know if there exists a similarly
> simple solution like the (last) section "Using both Python & Haskell
> with ctypes" at
> http://wiki.python.org/moin/PythonVsHaskell
> that works on Linux to easily link Haskell libraries/functions into
>
Duncan Coutts wrote:
>
>
>
> So it's easy if you link the system using ghc. If you want to link it
> all using gcc instead, yeah, that's a bit harder. You can see most of
> the flags ghc passes to gcc as they're just in the package configuration
> for the rts and base packages (ghc-pkg display
I've finished a good sized Haskell project which I now must expose as a
library (along with a lot of C code) to my fellow engineers. I had
originally devoped my code on Windows XP and managed to learn how to wrap my
Haskell code in a DLL and create an MSVC linkable library stub for the DLL.
Alth
Simon Marlow wrote:
>
> Tom Hawkins wrote:
>> I have a chunk of Haskell code I would like wrap up and distribute as
>> a library. Is there a way to build a static library (*.a) that
>> includes my code plus the Haskell runtime, which C programs can easily
>> link against? Here is what I have
a compiler flag, namely -fglasgow-exts.
>
>
> Cheers,
> Spencer Janssen
>
> On Tue, 13 Mar 2007 22:20:20 -0700 (PDT)
> SevenThunders <[EMAIL PROTECTED]> wrote:
>
>>
>> I have the pleasure of porting a good sized Haskell application to
>> linux
I have the pleasure of porting a good sized Haskell application to linux.
So far the Haskell code has compiled without incident, however some code
that I hacked
to implement a Read instance for Unboxed Arrays does not compile on linux
even though it compiles just fine on Windows XP in Haskell 6.6.
Donald Bruce Stewart wrote:
>
> mattcbro:
>
> Faster, and trivial to write! Here's a complete example:
>
> ...
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
Thanks for the
Neil Mitchell wrote:
>
>
> I found that Read was maybe 30 times slower than the slowest binary
> serialisation method I could possibly think of. If performance matters
> to you, and the array is more than a few elements long, switching away
> from Read/Show should be the first step - before go
Neil Mitchell wrote:
>
>
> The problem is that something like GHC is very complex, with lots of
> transformations. When transformations are firing other
> transformations, which in turn fire other transformations, it doesn't
> take a great deal to disrupt this flow of optimisation and end up wi
Donald Bruce Stewart wrote:
>
>
>
> Hmm, are you missing a -O ? Does that help at all?
>
> -- Don
>
>
>
Adding the -O does not stop the memory leak problem. As for the profiler,
it does make the CAF:main function show more erratic memory spikes, however
no memory ramping is revealed eve
Jason Dagit-2 wrote:
>
>
>
> Do any memory leaks show up if you compile with -caf-all when you profile?
>
> Jason
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
It doesn't
SevenThunders wrote:
>
> All my code is compiled using the -prof -auto
> flag and then run using +RTS -hc -RTS. The resulting plots do not show
> a linear increase in heap usage, although the Windows XP operating
> system does report such an increase.
>
>
This is e
David House wrote:
>
> On 06/10/06, SevenThunders <[EMAIL PROTECTED]> wrote:
>> Some of these functions are really annoying to write type declarations
>> for.
>> Maybe I'll get ghci to do it for me and use cut and paste :)
>
> Try using t
SevenThunders wrote:
>
>
>
> -- | compute cos (theta / 2) assuming the branch [-pi, pi]
> halfcos :: Double -> Double
> halfcos cs = sqrt $ (cs + 1)/2
>
> This produces a parse error
> parse error in doc string: [haddock.exe: reading EOF!
> on the h of t
Ivan Perez-4 wrote:
>
> Matthew Bromberg wrote:
>
>
> I can't help you about the haddock thing but, in my experience,
> if you forgive that kind of mistakes, many users will write
> documentation with
> lots of warnings and say "ok, these docs ain't right but, it works for
> me".
> I guess thi
SevenThunders wrote:
>
> I am trying to use Haddock for the first time on windows for a
> reasonably large project.
>
>
>
After playing around with this some, it appears that some of my parse errors
are occuring on functions
that have no explicit type declarations.
Krasimir Angelov-2 wrote:
>
> Hi Matthew,
>
> On Windows stdout/stderr/stdin exists only when your application is
> using the Console OS subsystem. All GUI applications doesn't have
> console window and they don't have stdout/stderr/stdin. When you are
> building DLLs then the subsystem is dete
SevenThunders wrote:
>
> I am having some difficulty with creating a dynamic link library using
> GHC on windows XP.
>
>
I am having some problems with GHCs stdout when a Haskell program is called
from a windows program.
As I noted earlier I am calling some Haskell c
SevenThunders wrote:
>
>
>
> SevenThunders wrote:
>>
>> I am having some difficulty with creating a dynamic link library using
>> GHC on windows XP.
>>
>>
>
>
> I need to report some additional strange DLL behavior with ghc.exe
SevenThunders wrote:
>
> I am having some difficulty with creating a dynamic link library using
> GHC on windows XP.
>
>
I need to report some additional strange DLL behavior with ghc.exe
unfortunately.
Although I solved my linking problems and was able to create a .dll a
SevenThunders wrote:
>
> I am having some difficulty with creating a dynamic link library using
> GHC on windows XP.
>
> I am attempting to follow the example in
> http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html
>
> though I have a binary
Jason Dagit wrote:
>
> On 9/27/06, SevenThunders <[EMAIL PROTECTED]> wrote:
>
>> Does cabal really work on windows?
>
> I've never had a problem with cabal on windows. I use it instead of
> makefiles and I'm reasonably happy with it.
>
>> Al
Jason Dagit wrote:
>
> On 9/26/06, Matthew Bromberg <[EMAIL PROTECTED]> wrote:
>> I am having some difficulty with creating a dynamic link library using
>> GHC on windows XP.
>>
>> I am attempting to follow the example in
>> http://www.haskell.org/ghc/docs/6.4/html/users_guide/win32-dlls.html
>
Well I tried this statement
ghc --mk-dll -fglasgow-exts -fffi -I. --make ExternLib.hs
It only compiled the object file, creating ExternLib.o, but it did not
create the stub file or attempt to link in the dependent packages. I then
went back to this,
ghc --mk-dll -fglasgow-exts -fffi -o netsim.
Florian Weimer wrote:
>
> * SevenThunders:
>
>> OK it was stupid. Apparently GHC behaves differently according to what
>> the
>> name of the high level source file is. If I renamed test.hc to main.hc
>> everything works the same as GHCi. I probably should
Yes I do have another test on my path. It is in a utilities directory of
unix like commands that have been ported to windows. However I also have a
test.exe that was created by ghc that seems to do nothing, even if I type
./test.exe. Thanks for the hint though.
--
View this message in context:
SevenThunders wrote:
>
> I have run into a baffling distinction between the behavior of GHCi and
> the compiled binary from GHC.
> I suspect it's something pretty stupid on my part.
>
> I have the following test program
>
> import Matrix
>
> main =
Sebastian Sylvan-2 wrote:
>
>
> Well, why would you want a huge array of random numbers?
> In Haskell there are two big ways to gain efficiency, strictness and
> laziness. In this case I think laziness is a big candidate (the "huge
> array" part gives it away).
> Also there is no reason generat
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 retrie
Alberto Ruiz-2 wrote:
>
> The GSL has been ported to Windows:
>
> http://gnuwin32.sourceforge.net/packages/gsl.htm
>
> so I think that GSLHaskell could also be adapted to work in Windows... I
> will
> try to do it.
>
> Alberto
>
> On Monday 24 July 2006
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 a
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
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 retrie
Are there Haskell specific tools for Eclipse? My experience so far has been
somewhat negative.
I tried to use eclipse with D some time ago, but the plugin kept crashing
and Eclipse seems to
have kind of a mind of it's own. I think for java development it's highly
regarded.
Everytime I try one
Has anyone actually seen ghc link successfully to third party libraries on
windows?
While I have been able to link to C object code compiled by ghc (and thus
gcc by proxy), I have not been able to actually link against any substantial
third party library or dll in windows.
I am currently attempti
Thanks for the gnuplot stuff. I intend to try that out. Perhaps sooner than
later.
As for lhs2tex, since no windows installer is provided, it might be a bit
trickier and my time
is very limited. Also after reviewing the manual it seems to still be
focused on literate programming more than active
Thats some good info. It probably should go on that wiki page.
All I need now is an unlimited amount of spare time...
--
View this message in context:
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420914
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
___
Aarrgh! Are the formatting commands the same?
I don't want to have to rewrite the whole thing.
That is a bit confusing.
--
View this message in context:
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420902
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
Done! Thanks for the tip.
I added a wiki page on this with my overly simple examples.
Perhaps I'll extend it as I learn more.
http://www.haskell.org/hawiki/FfiWithArrays
--
View this message in context:
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4402742
Sent from the Haskell - Has
Yup I'm aware of it, and I'd love to use it. The only problem is that it's
highly linux/unix specific as far as I can tell. Even the graphics
libraries it uses only runs on 'nix right now. I just tried to load
graphics.hgl and hello world program crashed GHCi and doesn't compile under
the regul
The rabbit hole goes a bit deeper I'm afraid
y :: CDouble
y = 5.2
u :: Double
u = realToFrac(y)
test = do printf "%14.7g" u
gives
Compiling Test ( test.hs, interpreted )
test.hs:14:11:
No instance for (PrintfType (t t1))
arising from use of `printf' at test.hs:14:11-16
Thanks that helps a bit. The realToFrac type coercion works, but ultimately
it seems
that printf won't play nice. Consider this simple haskell code
module Test
where
import IO
-- import Data.Array.Storable
import Text.Printf
import Foreign.C.Types (CInt, CDouble )
y :: CDouble
y = 5.
I am new to Haskell and found myself in a bind concerning the use of
the C types, CDouble in particular. I extract a CDouble via it's pointer
from a StorableArray. Since the array must interface with C the elements of
the array must be CDouble. Now I'd like to use Text.Printf to format print
s
66 matches
Mail list logo