
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

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

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

I did a writeup for an even simpler example, which hopefully will give you the right idea how to do it in your case: http://blog.ezyang.com/2011/12/accessing-lazy-structures-from/ Cheers, Edward

Hi, Edward.
Thank you very much for your help. Very concisely.Russian say: brevity is
the sister of talent. I made my own naive
solutionhttp://rsdn.ru/forum/decl/4543044.1.aspx which
based on VoidEx's advise http://rsdn.ru/forum/decl/4541766.1.aspx. In
Russian, but I think, you'll see the idea. It has some noise such as
CLazyList what is no more than code atavism from previous versions.
Happy hacking, too!
Alexander.
2011/12/16 Edward Z. Yang
I did a writeup for an even simpler example, which hopefully will give you the right idea how to do it in your case:
http://blog.ezyang.com/2011/12/accessing-lazy-structures-from/
Cheers, Edward
participants (2)
-
Alexander.Vladislav.Popov
-
Edward Z. Yang