Re: [Haskell-cafe] Why am I not allowed to use CStringLen inforeignexport?

2006-09-22 Thread Andreas Marth
Thanks a lot for this information it helped a lot.
Because I use the VBA 6 version the string characters are supposed to be a
byte so I changed your code to

type BSTR8 = Ptr Word8

createBSTR8 :: String - IO BSTR8
createBSTR8 s = do
   let
 len :: Word32 = fromIntegral (length s)
 low_l :: Word8 = fromIntegral (len .. 0x)
 low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
 high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
 high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
   arr - newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral .
fromEnum) s ++ [0])
   return $! plusPtr arr 4

Maybe this helps some one else too.
I am thinking about creating a wikipage about Haskell-VBA interfacing
through a DLL.
Is it okay for you if I put your code there?
I am a bit concerned about the memory. newArray states that the memory has
to be freed after usage. Is this needed here? How can it be done?

Thanks to everyone who responded,
Andreas



- Original Message -
From: Brian Hulley [EMAIL PROTECTED]
To: Andreas Marth [EMAIL PROTECTED]; haskell-cafe@haskell.org
Sent: Friday, September 15, 2006 10:07 PM
Subject: Re: [Haskell-cafe] Why am I not allowed to use CStringLen
inforeignexport?


 Brian Hulley wrote:
  I assume that this means that on 32 bit Windows, the format of a BSTR
  is:
  Word16 -- low word of length
  Word16 -- high word of length
  Word16 -- first char of string
   ...

 The above is not quite correct. It appears from
 http://www.oreilly.com/catalog/win32api/chapter/ch06.html that the length
 must preceed the actual BSTR, thus you must give VBA a pointer to the
first
 *char* in the string not the actual start of the array of Word16's in
 memory. Furthermore, it appears that a terminating NULL is still needed
even
 though the string itself can contain NULL characters. No only that, but
the
 length must be given as the number of *bytes* (excluding the terminating
 NULL) not the number of characters.

 Therefore here is a revised attempt at creating a Win32 BSTR:

 import Data.Word
 import Data.Bits
 import Foreign.Marshal.Array
 import Foreign.Ptr

 type BSTR = Ptr Word16

 createBSTR :: [Char] - IO BSTR
 createBSTR s = do
 let
 len :: Word32 = fromIntegral (length s * 2)
 low :: Word16 = fromIntegral (len .. 0x)
 high :: Word16 = fromIntegral (shiftR len 16 .. 0x)
 arr - newArray ([low, high] ++ map (fromIntegral . fromEnum) s ++
 [0])
 return $! plusPtr arr 4

 foreign export stdcall hello :: IO BSTR
 hello :: IO BSTR
 hello = createBSTR Hello world!

 Regards, Brian.


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


[Haskell-cafe] Re: [newbie] How to test this function?

2006-09-22 Thread Jón Fairbairn
Bruno Martínez [EMAIL PROTECTED] writes:

 On Thu, 21 Sep 2006 15:12:07 -0300, Benjamin Franksen
 [EMAIL PROTECTED] wrote:
 
  OK.  Thanks.  I didn't find that one because it's not offered as an
  identation option in emacs haskell mode.
 
  Emacs is evil!

That's a great exaggeration

 I'm open to alternatives.  I use Windows, so went out of the
 way to have  emacs.  What do you use?  I don't care much for
 colors, but automatic  identation is very handy (when it
 works :D).

If there's a problem with haskell emacs mode, it seems very
likely that if you ask the maintainer nicely, he'll do
something about it. See
http://www.iro.umontreal.ca/~monnier/elisp/#haskell-mode

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-09-13)

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


[Haskell-cafe] Haskell DLL crashes Excel

2006-09-22 Thread Andreas Marth
Hi everybody!

As you might now already know I try to let VBA call Haskell via a DLL. The
function returns a String. Everything works fine now if I call the function
only once. If I call it more often Excel crashes soon. Does any body have
any idea what is going wrong or how I can find out. (I am a medium skilled
Haskell user but no VBA programmer.)

My code for Haskell (Calculate.hs):

module Calculate where

import Foreign.C.String (CString, peekCString, newCString)
import Data.Word (Word8, Word16, Word32)
import Data.Bits (shiftR, (..))
import Foreign.Marshal.Array (newArray)
import Foreign.Ptr (Ptr, plusPtr)

type BSTR8 = Ptr Word8

createBSTR8 :: String - IO BSTR8
createBSTR8 s = do
   let
 len :: Word32 = fromIntegral (length s)
 low_l :: Word8 = fromIntegral (len .. 0x)
 low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
 high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
 high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
   arr - newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral .
fromEnum) s ++ [0])
   return $! plusPtr arr 4


testL :: Int - CString - IO BSTR8
testL n cs = do s - peekCString cs
createBSTR8 $ concat $ take n $ repeat s

foreign export stdcall testL :: Int - CString - IO BSTR8

---

My VBA code (in Excel 2000):

Option Explicit

Dim h1 As String
Dim a As Long
Dim b As Long

Private Declare Function testL Lib P:\Daten\Code\Calculate.dll (ByVal n As
Long, ByVal str As String) As String

Sub Test()
a = 0
b = 10
h1 = 
Do While a = 15
h1 = testL(b, What is going on here?)
a = a + 1
Debug.Print a
Debug.Print h1
Loop
End Sub

---

And my DllMain.c:

#include windows.h
#include Rts.h

extern void __stginit_Calculate(void);

static char* args[] = { ghcDll, NULL };
   /* N.B. argv arrays must end with NULL */
BOOL
STDCALL
DllMain
   ( HANDLE hModule
   , DWORD reason
   , void* reserved
   )
{
  if (reason == DLL_PROCESS_ATTACH) {
  /* By now, the RTS DLL should have been hoisted in, but we need to
start it up. */
  startupHaskell(1, args, __stginit_Calculate);
  return TRUE;
  }
  if (reason == DLL_PROCESS_DETACH) {
  shutdownHaskell();
  return TRUE;
  }
  return TRUE;
}



And I compile the DLL with:

ghc -c --make -fglasgow-exts -static Calculate.hs
ghc -c -fglasgow-exts -static *.c
ghc --mk-dll -o Calculate.dll *.o -static -optdll--def -optdllCalculate.def

--

Nearly forgot Calculte.def:

LIBRARY Calculate
EXPORTS
testL = [EMAIL PROTECTED]

-

The DLL is stable regarding the length of the input string and thelength of
the return string (determined with b).
But crashes for larger(?) a's. At my computer it crashes with a 9.

There seems to be a connection between b and a. If b is 10 then a9 crashes
a10 is fine.
If b=1000  then a5 is okay a4 crashes.
If b =100 then a5 is okay, a5 crashes and a=5 crashes with an error
Statement in 0x778cb032 points to 0x the function 'written' could
not be done ... And a second one Statement in 0x778cc441 points to
0x the function 'written' could not be done ... (My translation of
the german errors.)


If anybody knows what is going wrong or can give me a hint how to find out
what is going wrong it would be very helpful.
Thanks Andreas

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


Re: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-22 Thread Kyra

Andreas Marth wrote:


type BSTR8 = Ptr Word8

createBSTR8 :: String - IO BSTR8
createBSTR8 s = do
   let
 len :: Word32 = fromIntegral (length s)
 low_l :: Word8 = fromIntegral (len .. 0x)
 low_h :: Word8 = fromIntegral (shiftR len 8 .. 0x)
 high_l :: Word8 = fromIntegral (shiftR len 16 .. 0x)
 high_h :: Word8 = fromIntegral (shiftR len 24 .. 0x)
   arr - newArray ([low_l,low_h,high_l,high_h] ++ map (fromIntegral .
fromEnum) s ++ [0])
   return $! plusPtr arr 4


Use SysAllocString... family. Also, remember they (by convention) have 
to be released from the client side.


Cheers,
Kyra


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


Re: [Haskell-cafe] Re: [newbie] How to test this function?

2006-09-22 Thread Johan Tibell

If there's a problem with haskell emacs mode, it seems very
likely that if you ask the maintainer nicely, he'll do
something about it. See
http://www.iro.umontreal.ca/~monnier/elisp/#haskell-mode


I asked Stefan a while ago:


I like your Emacs mode but it behaves a bit oddly when trying to
indent if/then/else expressions in do notation. Typing tab only gives
me one possible indentation, like so:



do if True
   then foo
   else bar



That is, the then and else branches line up under the if which is an
error according to Haskell's layout rule. It probably should indent
them like case with the then lining up with the condition to the if.
I'd fix it myself if I knew Lisp but I don't. :/


Yes, it's a (recently) known problem which I haven't fixed yet.
It's in the indent.hs test-suite, with a FIXME :-(
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskore

2006-09-22 Thread Henning Thielemann

On Fri, 22 Sep 2006, David Curran wrote:

 Hi
 I have been trying to learn haskell (tip over the vending machine) for
 a while and eventually decided the Haskore music library might be a
 good way to start understating the language.

Please, don't understate this language! ;-)

 I am using windows and hugs98. The IOExtensions.hs file will not work
 under windows. Any ideas on how to make it work or is this library
 *nix only?

I think that this problem was resolved in the revised Haskore version, see
 http://darcs.haskell.org/haskore/
   and its binary file wrapper
 http://darcs.haskell.org/haskore/src/Haskore/General/IO.hs

However, I feel that this Haskore version is no longer simple enough for
learning.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell DLL crashes Excel

2006-09-22 Thread Kyra

Kyra wrote:
Use SysAllocString... family. Also, remember they (by convention) have 
to be released from the client side.


Oops, they = such allocated BSTRs.

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


[Haskell-cafe] Re: [newbie] How to test this function?

2006-09-22 Thread Jón Fairbairn
Johan Tibell [EMAIL PROTECTED] writes:

  If there's a problem with haskell emacs mode, it seems very
  likely that if you ask the maintainer nicely, he'll do
  something about it. See
  http://www.iro.umontreal.ca/~monnier/elisp/#haskell-mode
 
 I asked Stefan a while ago:
 
  I like your Emacs mode but it behaves a bit oddly when trying to
  indent if/then/else expressions in do notation. Typing tab only gives
  me one possible indentation, like so:
 
  do if True
 then foo
 else bar
 
  That is, the then and else branches line up under the if which is an
  error according to Haskell's layout rule. It probably should indent
  them like case with the then lining up with the condition to the if.
  I'd fix it myself if I knew Lisp but I don't. :/
 
 Yes, it's a (recently) known problem which I haven't fixed yet.
 It's in the indent.hs test-suite, with a FIXME :-(

For that one, if it doesn't get mended for long enough,
Haskell' might accept the present layout.
http://hackage.haskell.org/trac/haskell-prime/wiki/DoAndIfThenElse

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2006-09-13)

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


[Haskell-cafe] Re: Haskore

2006-09-22 Thread Jón Fairbairn
David Curran [EMAIL PROTECTED] writes:

 Hi
 I have been trying to learn haskell (tip over the vending machine)

Tipping over a vending machine is a real world effect, so
you'll have to use the IO Monad.

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskore

2006-09-22 Thread Bulat Ziganshin
Hello David,

Friday, September 22, 2006, 1:40:31 PM, you wrote:

 openBinaryFile :: FilePath - IOMode - IO Handle

import System.IO

 writeBinaryFile  :: FilePath - String - IO ()
writeBinaryFile f txt = bracket (openBinaryFile f WriteMode) hClose
(\hdl - hPutStr hdl txt)

 readBinaryFile   :: FilePath - IO String
readBinaryFile name   = openBinaryFile name ReadMode = hGetContents

these definitions will work both on unix and win





-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Haskore

2006-09-22 Thread Paul Hudak




As Henning points out, the darcs version of Haskore is now the
standard, which Henning has been kind enough to set up. However, it
has also been extended and re-organized, and at least currently does
not have the simplistic feel of the original Haskore. On the other
hand, the version that is described in Chapter 20 of SOE (which is
called "MDL") is very simple and elegant and would be a great way to
"learn Haskell". Even though it's in Chapter 20, it depends only on
material presented much earlier in the book.

I hope this helps, -Paul


Henning Thielemann wrote:

  On Fri, 22 Sep 2006, David Curran wrote:
  
Hi
I have been trying to learn haskell (tip over the vending machine) for
a while and eventually decided the Haskore music library might be a
good way to start understating the language.

  
  
I am using windows and hugs98. The IOExtensions.hs file will not work
under windows. Any ideas on how to make it work or is this library
*nix only?

  
  
I think that this problem was resolved in the revised Haskore version, see
 http://darcs.haskell.org/haskore/
   and its binary file wrapper
 http://darcs.haskell.org/haskore/src/Haskore/General/IO.hs

However, I feel that this Haskore version is no longer simple enough for
learning.



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


Re: [Haskell-cafe] Haskore microtonal support

2006-09-22 Thread Paul Hudak
An easier and better way to support microtonal music in Haskore is to 
use the csound back-end instead of MIDI.  I'd be happy to help someone 
develop such a thing if interested.


   -Paul

Magnus Jonsson wrote:


On Thu, 14 Sep 2006, Henning Thielemann wrote:


On Thu, 14 Sep 2006, Magnus Jonsson wrote:


Now even more interestingly, my program also deals with music! :) I'm
generating microtonal midi files. I use it for very much the same 
purpose as

you do (although my program is not yet finished).


Is it something we could and should add to Haskore?


If Haskore could support microtones that would make this world a 
slightly better world for me. Here are the basic things you need to 
support microtonal music:


- Pitch representations would have to be able to express any pitch.
  - One appealing approach is to represent a pitch directly as it's 
frequency.

  - Probably the most useful representation though is a base pitch,
say one of C,D,E,F,G,A,B, followed by a list of accidentals that
modify the pitch. The user should be able to define his own base
pitches and accidentals, in terms of cents or frequency ratios or
something similar.
- Generating microtonal midi files requires that you add pitch-bend 
messages before all notes. That restricts each midi channel to only 
being able to play one note at a time. This is a big deficiency in the 
midi protocol imo.


/ Magnus 



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


[Haskell-cafe] Re: Haskel DLL crashes Excel

2006-09-22 Thread Cyril Schmidt
Andreas Marth wrote:
 As you might now already know I try to let VBA call Haskell via a DLL.

I had to do this a while ago; the best I could come up with was:

1. Make a Haskell DLL that exports plain C-style interface.

2. With Visual Studio, make a COM DLL that exports the interfaces to
be used by VBA and passes the calls to the Haskell DLL. This COM DLL,
among other things, handles the conversion between C-style strings
and BSTR (there are examples on msdn.microsoft.com of doing this).

Hope this helps.

Cheers,

Cyril

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


Re: [Haskell-cafe] Why am I not allowed to use CStringLen inforeignexport?

2006-09-22 Thread Brian Hulley

Andreas Marth wrote:

Thanks a lot for this information it helped a lot.


Glad to be of help.


I am thinking about creating a wikipage about Haskell-VBA
interfacing through a DLL.
Is it okay for you if I put your code there?


Yes.


I am a bit concerned about the memory. newArray states that the
memory has to be freed after usage. Is this needed here? How can it
be done?


One way could be to write a function which creates the BSTR, passes it to a 
function, then deallocates the BSTR before returning eg (untested):


   import Control.Exception (bracket)

   withBSTR8 :: [Char] - (BSTR8 - IO a) - IO a
   withBSTR8 s f =
   bracket
   (createBSTR8 s)
   (\bstr - free (bstr `plusPtr` (-4)))
   (\bstr - f bstr)

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