Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Compiling shared (dll) library (Daniel Fischer)
   2. Re:  FFI export lazy list of string (Edward Z. Yang)
   3. Re:  FFI export lazy list of string (Alexander.Vladislav.Popov )


----------------------------------------------------------------------

Message: 1
Date: Mon, 5 Dec 2011 15:19:30 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Compiling shared (dll) library
To: "Alexander.Vladislav.Popov " <[email protected]>
Cc: [email protected]
Message-ID: <[email protected]>
Content-Type: Text/Plain;  charset="utf-8"

On Monday 05 December 2011, 13:44:25, Alexander.Vladislav.Popov wrote:
> > Why the separate compilation? Can't you compile them in one go?
> 
>  Sorry for a stupid question, how is it?

Not stupid at all.

I'm not an expert in matters FFI, so I don't know if it works in all 
situations, but for simple cases at least, you can compile in one go 
listing .hs and .c files on the command line.

For a foreign import:

// hsFibo.hs:
{-# LANGUAGE ForeignFunctionInterface #-}
module Main (main) where

import System.Environment (getArgs)

foreign import ccall unsafe "fibo"
    c_fibo :: Int -> Int

main :: IO ()
main = do
    args <- getArgs
    let n = case args of
              (a:_) -> read a
              _ -> 14
    print (c_fibo n)

// Fibonacci.c
int fibo(int n){
    int a = (n&1) ? 0 : 1, b = (n&1) ? 1 : 0;
    while(n > 1){
        a += b;
        b += a;
        n -= 2;
    }
    return b;
}

$ ghc -O2 hsFibo.hs Fibonacci.c 
[1 of 1] Compiling Main             ( hsFibo.hs, hsFibo.o )
Linking hsFibo ...
$ ./hsFibo 21
10946

For a foreign export it's a bit more complicated, as you would have to 
generate the .h file(s) first by other means (if all your exported 
functions are compatible with the implicit types for C functions [pre C99, 
iirc], you can get away without the header, but you'll get warnings about 
implicit declarations). But with appropriate headers, you can compile in 
one go,

$ ghc -O2 -shared -dynamic -fPIC Export.hs useExport.c -o theexport.so

(if you use a C main to create an executable, also pass -no-hs-main).

> 
> And one more question, please: how I can export genexPure :: [String] ->
> [String] to achieve all preferences of lazy list? Not all array at once,
> but to get someting like an iterator, what I can call to get new genex.

Pass. I have no idea how to do that.




------------------------------

Message: 2
Date: Mon, 05 Dec 2011 14:13:07 -0500
From: "Edward Z. Yang" <[email protected]>
Subject: Re: [Haskell-beginners] FFI export lazy list of string
To: "Alexander.Vladislav.Popov" <[email protected]>
Cc: beginners <[email protected]>
Message-ID: <1323112216-sup-8502@ezyang>
Content-Type: text/plain; charset=UTF-8

Hello Alexander,

Your best bet is to make a Haskell functions which gives access to
the head and tail of a list (the head should be converted into a C-friendly
form) and then export them as functions which are callable from C.

http://www.haskell.org/haskellwiki/GHC/Using_the_FFI#Calling_Haskell_from_C

Edward

Excerpts from Alexander.Vladislav.Popov's message of Mon Dec 05 03:08:59 -0500 
2011:
> Hi, Haskellers.
> 
> Advise me please, how I can export lazy and potentially infinite list of
> string from Haskell program. I think I must call it iteratively: the first
> call initiate some structure and other calls iterate over it, something
> like pair of function `find_first' and `find_next'. And how to marshall
> this structure between programs. Or think in a wrong way? Does any example
> exist how I can make it?
> 
> Alexander Popov



------------------------------

Message: 3
Date: Tue, 6 Dec 2011 12:43:58 +0600
From: "Alexander.Vladislav.Popov "
        <[email protected]>
Subject: Re: [Haskell-beginners] FFI export lazy list of string
To: "Edward Z. Yang" <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
        <calpbq9zlrw+ltoqyb1+pnecyl-hxzbjmn86wdzgrgn0v1zl...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hello Edward,

Would you help me to map this:

-- genexlib.hs
{-# LANGUAGE BangPatterns, ForeignFunctionInterface #-}

module GenexLib where

import Regex.Genex
import System.IO
import System.Environment

data CLazyList a = Empty | CLL !a [a]

instance (Show a) => Show (CLazyList a) where
  show Empty = "Empty"
  show (CLL x xs) = show x ++ ":.."

next (CLL _ [])     = Empty
next (CLL _ (x:xs)) = CLL x xs

fromList []     = Empty
fromList (x:xs) = CLL x xs

open = fromList . genexPure
-- end genexlib.hs

to

-- genex.c
typedef struct CLL {
  unsigned char empty;
  char          *current;
  struct CLL    *next;
} CLL;

CLL *open(const char *regex);
CLL *next(const CLL  *cll);

// void printf(const char *s, ...);

void usage() {
  CLL *genex = open("\\d+");
  while(!genex->empty) {
    printf(genex->current);
    genex = next(genex->next);
  }
}
-- end genex.c

Alexander Popov


2011/12/6 Edward Z. Yang <[email protected]>

> Hello Alexander,
>
> Your best bet is to make a Haskell functions which gives access to
> the head and tail of a list (the head should be converted into a C-friendly
> form) and then export them as functions which are callable from C.
>
> http://www.haskell.org/haskellwiki/GHC/Using_the_FFI#Calling_Haskell_from_C
>
> Edward
>
> Excerpts from Alexander.Vladislav.Popov's message of Mon Dec 05 03:08:59
> -0500 2011:
> > Hi, Haskellers.
> >
> > Advise me please, how I can export lazy and potentially infinite list of
> > string from Haskell program. I think I must call it iteratively: the
> first
> > call initiate some structure and other calls iterate over it, something
> > like pair of function `find_first' and `find_next'. And how to marshall
> > this structure between programs. Or think in a wrong way? Does any
> example
> > exist how I can make it?
> >
> > Alexander Popov
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111206/4ac4ef31/attachment-0001.htm>

------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 42, Issue 7
****************************************

Reply via email to