Re: [Haskell-cafe] FFI question - FunPtrs to top-level functions

2011-08-18 Thread kyra

On 8/18/2011 6:49 AM, Antoine Latter wrote:

Hi Haskell,

I have a question about the Haskell FFI and creating FunPtrs to
Haskell functions.

Does anyone have any recommendations for when I have a top-level
function that I would like to pass to a C function as a function
pointer (that is called via a foreign import)?

I know that the FFI provides the "wrapper" foreign import I can use to
wrap Haskell functions, but then I would need to jump through hoops to
manage the liefetime of of the FunPtr wrapper. If I were closing over
interesting state I would want this - but the function
(side-effectfully) operates only on its arguments (and the Haskell
RTS, of course).

Is it "okay" to place an "unsafePerformIO $ mkWrapper myFunc" as a
top-level declaration, or am I journeying into uncharted lands?

Is there something clever I can do with foreign exports and foreign
imports, or is this just making things too complex?

Thanks,
Antoine

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

You can export and reimport the same function with no "wrapper" needed. 
For example:


foreign export ccall foo :: ...
foreign import ccall "& foo" fooptr :: FunPtr (...)

Cheers,
Kyra

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


Re: [Haskell-cafe] Existential question

2011-08-18 Thread Miguel Mitrofanov
> Now, what we can do with kl1? We can feed it an integer, say 1, and
> obtain function f of the type s -> (s,Bool) for an _unknown_ type s.
> Informally, that type is different from any concrete type. We can
> never find the Bool result produced by that function since we can
> never have any concrete value s. The only applications of f that will
> type check are
>   \s -> f s
>   f undefined
> both of which are useless to obtain f's result.

That's not true. We can tie the knot:

let (s, o) = f s in o


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


[Haskell-cafe] conditionally exposing modules in cabal

2011-08-18 Thread Rogan Creswick
I would like to conditionally expose a number of internal modules in a
library depending on a cabal flag - the idea is that new features
could be implemented externally to the library without contaminating
the source with undesirable changes.  However, I've been unable to
find a way to structure a cabal file that does not require repeating
the list of modules.  For example, this works:

  exposed-modules:
Public.Stable.Module
  if flag(exposeInternals)
exposed-modules:
   
  else
other-modules:
   

But I don't want to maintain two identical lists of modules in the cabal file.

I've tried putting the section headers in the if's, but this doesn't
appear to work (cabal doesn't complain, but the modules to be exposed
are not available as expected):

  exposed-modules:
Public.Stable.Module
  if flag(exposeInternals) {
  exposed-modules:
  } else {
  other-modules:
  }



Does anyone have suggestions?

Thanks!
Rogan

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


Re: [Haskell-cafe] conditionally exposing modules in cabal

2011-08-18 Thread Antoine Latter
On Thu, Aug 18, 2011 at 3:33 AM, Rogan Creswick  wrote:
> I would like to conditionally expose a number of internal modules in a
> library depending on a cabal flag - the idea is that new features
> could be implemented externally to the library without contaminating
> the source with undesirable changes.  However, I've been unable to
> find a way to structure a cabal file that does not require repeating
> the list of modules.  For example, this works:
>

One problem to consider - a downstream user of the new features won't
know that they need to pass special flags to your module, and may not
even know that they are using your module if the dependency is a few
steps removed.

What some folks have taken to doing is to either turn of Haddock
documentation for the modules (as in Data.ByteString.Internal) or just
provide great big warning messages that the functions provided can be
used in ways which do not provide key invariants and that the contents
of the module is subject to change at any time.

Antoine

>  exposed-modules:
>    Public.Stable.Module
>  if flag(exposeInternals)
>    exposed-modules:
>       
>  else
>    other-modules:
>       
>
> But I don't want to maintain two identical lists of modules in the cabal file.
>
> I've tried putting the section headers in the if's, but this doesn't
> appear to work (cabal doesn't complain, but the modules to be exposed
> are not available as expected):
>
>  exposed-modules:
>    Public.Stable.Module
>  if flag(exposeInternals) {
>  exposed-modules:
>  } else {
>  other-modules:
>  }
>    
>
>
> Does anyone have suggestions?
>
> Thanks!
> Rogan
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

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


Re: [Haskell-cafe] conditionally exposing modules in cabal

2011-08-18 Thread Rogan Creswick
On Thu, Aug 18, 2011 at 4:41 AM, Antoine Latter  wrote:
> One problem to consider - a downstream user of the new features won't
> know that they need to pass special flags to your module, and may not
> even know that they are using your module if the dependency is a few
> steps removed.

The situation is more that I have a number of independent changes that
I'd like to experiment with locally, without ever releasing them
individually -- if/when they're released, they would build without the
need to set the flag.  The net effect is very similar to maintaining
multiple branches of the primary project, but with more separation
between the stable project and the experimental code.

--Rogan

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


[Haskell-cafe] Gaussian elimination

2011-08-18 Thread Tobias Nipkow
Hi, I came up with the following extremely compact version of Gaussian
elimination for matrices represented as functions. I searched the web
but found nothing resembling it, probably because of its inefficiency.
Has anybody seen something like it before?

Thanks
Tobias

gauss :: Int -> (Int -> Int -> Rational) -> Maybe (Int -> Int -> Rational)
gauss 0 a = Just a
gauss (n+1) a =
  case dropWhile (\i -> a i n == 0) [0..n] of
[] -> Nothing
(k:_) ->
  let ak' j = a k j / a k n
  a' i = if i == k then ak' else (\j -> a i j - a i n * ak' j)
  in gauss n (swap k n a')

swap :: Int -> Int -> (Int -> a) -> (Int -> a)
swap k n f = g
  where g x | x == k = f n
| x == n = f k
| otherwise = f x

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


Re: [Haskell-cafe] writing a good Setup.hs is *hard* (was: broken on install encoding 0.6.6)

2011-08-18 Thread malcolm.wallace
On 17 Aug, 2011,at 03:11 PM, Rogan Creswick  wrote:encoding-0.6.6 uses it's own source during the build process! It
actually has to be partially compiled before the build tool can build
encoding (!).  I'm *amazed* that this actually works at all
(impressed, too),  This is by design.  It is intended that when the Cabal library itself is configured and built by an existing installation of Cabal, the installation process can make use of the newer features in the current sources, rather than being restricted to bootstrapping with some arbitrary previous version.  So in general, you can distribute a self-contained package that contains the code/tools needed to build itself.  (As you note, this does not work out so well if those build tools are not self-contained, but depend on not-yet-installed packages.)issues in HaXml 1.19 (pretty is an undocumented dependency, although I
am unsure if that was true at the time 1.19 and encoding-0.6.6 were
released.The first version of the pretty package (split from base) was uploaded to hackage on 3rd Nov 2007.HaXml-1.19 was uploaded to hackage on 23rd Oct 2007.So yes, the dependencies of HaXml-1.19 were correct when it was released.  HaXml-1.19.2 was the first release to support the newly split pretty/base, in January 2008.However encoding-0.6.6 was released in June 2011, so I would say that its dependency on HaXml >= 1.19 must be bogus, and should be at least >= 1.19.2  (and you'll find that the current HaXml won't work for the current
encodings release, as Gang Yu did). I apologise that there are a number of 1.22.* releases of HaXml that do not build at all with ghc-7.x.  I believe 1.22.5 should fix all of the build issues.  (The only differences between 1.22.* releases arebuild-system and documentation related.)If the encodings package does not work with HaXml-1.22.5 for some other reason, then perhaps there is some API change, which means that encodings' dependency on HaXml should have a stricter upper bound.Regards,    Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Embedding Perl RegEx in Haskell

2011-08-18 Thread C K Kashyap
Dear Haskell folks,

I was attempting to do an EDSL that would allow me to describe regular
expressions in Hakell and generate Perl as target -

https://github.com/ckkashyap/LearningPrograms/blob/master/Haskell/edsl/regex.hs

$ ghci regex.hs
GHCi, version 7.0.3: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
[1 of 1] Compiling Main ( regex.hs, interpreted )
Ok, modules loaded: Main.
*Main> let hello = stringToRegularExpression "hello"
*Main> let world = stringToRegularExpression "world"
*Main> :t hello
hello :: RegularExpression
*Main> :t world
world :: RegularExpression
*Main> let re = listToSequence [ hello, oneOrMore world, hello ]
*Main> re
hello(world)+hello
*Main> :t re
re :: RegularExpression

I am looking for suggestions on how I could encode the anchors - ^ and $ and
also how I could refer to captures. My goal is to be able to extend the idea
to create an EDSL that could be used to build Perl tasks - such as filters,
report generators etc

Arguably this could be seen as a pointless exercise because I could chose to
do the scripting in Haskell itself but I have a practical problem that I
have to deal with clusters that have a little dated version of Linux where I
could not really build the Haskell and where Haskell generated executables
don't seem to run. When I started out with this idea, I was thinking of
embedding Perl in Haskell but later I thought that perhaps that will sort of
beat the point of "DS" bit in EDSL. So, I have started on this idea of
trying to encode very precise "tasks".

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


Re: [Haskell-cafe] Compilation error in Chapter 5 of "Real World Haskell"

2011-08-18 Thread Jason Dagit
On Wed, Aug 17, 2011 at 10:37 AM, Paul Reiners  wrote:
> I'm trying to do the following from Chapter 5 of "Real World Haskell":
>
> Our choice of naming for the source file and function is deliberate. To
> create an executable, ghc expects a module named Main that contains a
> function named main. The main function is the one that will be called when
> we run the program once we've built it. 6 comments
>
> ghc -o simple Main.hs SimpleJSON.o
>
> ---from
> http://book.realworldhaskell.org/read/writing-a-library-working-with-json-data.html
>
> When I do that, I get this error:
>
> C:\ch05>ghc -o simple Main.hs SimpleJSON.o
> [2 of 2] Compiling Main ( Main.hs, Main.o )
> Linking simple.exe ...
> SimpleJSON.o:fake:(.data+0x0): multiple definition of
> `SimpleJSON_getArray_closure'
> .\SimpleJSON.o:fake:(.data+0x0): first defined here
> SimpleJSON.o:fake:(.text+0x54): multiple definition of
> `SimpleJSON_getArray_info'
> .\SimpleJSON.o:fake:(.text+0x54): first defined here
> SimpleJSON.o:fake:(.data+0x4): multiple definition of
> `SimpleJSON_getObject_closure'
> .\SimpleJSON.o:fake:(.data+0x4): first defined here
>
> What's going wrong here?

It's hard to say without being able to compile your example locally.
Could you post the exact files Main.hs and SimpleJSON.hs that you are
using?  I scanned the linked page but it wasn't obvious to me what was
in your source files.

Jason

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


Re: [Haskell-cafe] Compilation error in Chapter 5 of "Real World Haskell"

2011-08-18 Thread Thomas DuBuisson
This is a linking issue.  It seems GHC 7 automatically feeds the
linker SimpleJSON.o so when you explicitly provide it too then you get
those conflicts.  All you need to do is call:

> ghc -o simple Main.hs

Unless you're using GHC 6, then the original command is correct:

> ghc -o simple Main.hs SimpleJSON.o

Or even better, use the --make flag as that works with either version:

> ghc --make -o simple Main.hs

Cheers,
Thomas

On Wed, Aug 17, 2011 at 10:37 AM, Paul Reiners  wrote:
> I'm trying to do the following from Chapter 5 of "Real World Haskell":
>
> Our choice of naming for the source file and function is deliberate. To
> create an executable, ghc expects a module named Main that contains a
> function named main. The main function is the one that will be called when
> we run the program once we've built it. 6 comments
>
> ghc -o simple Main.hs SimpleJSON.o
>
> ---from
> http://book.realworldhaskell.org/read/writing-a-library-working-with-json-data.html
>
> When I do that, I get this error:
>
> C:\ch05>ghc -o simple Main.hs SimpleJSON.o
> [2 of 2] Compiling Main ( Main.hs, Main.o )
> Linking simple.exe ...
> SimpleJSON.o:fake:(.data+0x0): multiple definition of
> `SimpleJSON_getArray_closure'
> .\SimpleJSON.o:fake:(.data+0x0): first defined here
> SimpleJSON.o:fake:(.text+0x54): multiple definition of
> `SimpleJSON_getArray_info'
> .\SimpleJSON.o:fake:(.text+0x54): first defined here
> SimpleJSON.o:fake:(.data+0x4): multiple definition of
> `SimpleJSON_getObject_closure'
> .\SimpleJSON.o:fake:(.data+0x4): first defined here
>
> What's going wrong here?
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

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


Re: [Haskell-cafe] Embedding Perl RegEx in Haskell

2011-08-18 Thread Brandon Allbery
On Thu, Aug 18, 2011 at 14:01, C K Kashyap  wrote:

> *Main> let re = listToSequence [ hello, oneOrMore world, hello ]
> *Main> re
> hello(world)+hello
>
> I am looking for suggestions on how I could encode the anchors - ^ and $
> and also how I could refer to captures. My goal is to be able to extend the
> idea to create an EDSL that could be used to build Perl tasks - such as
> filters, report generators etc
>

Why not just go with anchorHead and anchorTail or similar?  And a capture
could simply be

 capture name regularExpression

where name can be an Int or support the newer named capture syntaxes.  I'm
not sure I would bother with fancy symbols; if anything, I might in your
position go back to the old v8 regular expressions (or rather Henry
Spencer's unencumbered reimplementation) and use the symbolic names from
that; they were actually virtual machine opcodes.

(Or even

capture (Maybe name) regularExpression

and (capture Nothing ...) could represent grouping.  That's certainly how
many actual RE implementations define it.)

Arguably this could be seen as a pointless exercise because I could chose to
> do the scripting in Haskell itself but I have a practical problem that I
> have to deal with clusters that have a little dated version of Linux where I
> could not really build the
>

(Don't even get me started on Linux backward incompatibility... I spent
years fighting that crap, it's one thing I do not at all miss from my old
job.)

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Failed link to mixed-language shared object.

2011-08-18 Thread David Banas
Hi all,

Does this trigger recollection in anyone:

dbanas@dbanas-eeepc:~/prj/haskell/AMIParse/trunk$ make
ghc -dynamic -o ami_test -L. -lami ami_test.o
./libami.so: undefined reference to `__stginit_haskell98_MarshalArray_'
./libami.so: undefined reference to `__stginit_haskell98_MarshalError_'
collect2: ld returned 1 exit status
make: *** [ami_test] Error 1
dbanas@dbanas-eeepc:~/prj/haskell/AMIParse/trunk$ 

?
Know what I need to do?

Thanks,
-db



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


Re: [Haskell-cafe] Failed link to mixed-language shared object.

2011-08-18 Thread Brandon Allbery
On Thu, Aug 18, 2011 at 23:32, David Banas  wrote:

> Does this trigger recollection in anyone:
>
> dbanas@dbanas-eeepc:~/prj/haskell/AMIParse/trunk$ make
> ghc -dynamic -o ami_test -L. -lami ami_test.o
> ./libami.so: undefined reference to `__stginit_haskell98_MarshalArray_'
> ./libami.so: undefined reference to `__stginit_haskell98_MarshalError_'
>

First thing to try is always --make; GHC's default behavior is, shall we
say, not optimal otherwise.  (I consider it highly broken; somewhere in
there the default is *supposedly* going to change to --make, I believe.)  If
you want to try to make it work the ugly old way, the symbol names suggest
to me that "-package haskell98" would help.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] custom SQL-to-Haskell type conversion in HDBC

2011-08-18 Thread Henry House
Does there exist any sample code or other resources on writing a custom
SQL-to-Haskell datatype converter instance for use with HDBC that would be
accessible to someone just starting with Haskell? The reason I need this is
because of this problem (using PostgreSQL):

Prelude Database.HDBC.PostgreSQL Database.HDBC> res <- (quickQuery db "select 
1::numeric(5,4);" [])
Prelude Database.HDBC.PostgreSQL Database.HDBC> res
[[SqlRational (1 % 1)]]
Prelude Database.HDBC.PostgreSQL Database.HDBC> res <- (quickQuery db "select 
1::numeric(5,0);" [])
[[SqlRational (1 % 1)]]

where db is a database connection. The SQL values 1::numeric(5,4) and
1::numeric(5,0) are supposed to be fixed-precision numbers having 4 and zero
significant decimal figures after the decimal point, respectively. Both are
offered by HDBC as the same SqlValue, SqlRational (1 % 1) but they are not
really the same at all. The precision information has been lost. The native
outputs of PostgreSQL, before HDBC's type conversion, are 1. and 1 for
'select 1::numeric(5,4);' and 'select 1::numeric(5,0);', respectively.

-- 
Henry House

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


Re: [Haskell-cafe] Existential question

2011-08-18 Thread Ryan Ingram
On Wed, Aug 17, 2011 at 4:49 PM, Tom Schouten  wrote:

> {-# LANGUAGE ExistentialQuantification #-}
>
> -- Dear Cafe, this one works.
> data Kl' s i o = Kl' (i -> s -> (s, o))
> iso' :: (i -> Kl' s () o) -> Kl' s i o
> iso' f = Kl' $ \i s -> (\(Kl' kl') -> kl' () s) (f i)
>
> -- Is there a way to make this one work also?
> data Kl i o = forall s. Kl (i -> s -> (s, o))
> iso :: (i -> Kl () o) -> Kl i o
> iso f = Kl $ \i s -> (\(Kl kl) -> kl () s) (f i)
>

Not without moving the quantifier, as Oleg says.  Here is why:

Existential types are equivalent to packing up a type with the constructor;
imagine KI as

data KI i o = KI @s (i -> s -> (s,o))   -- not legal haskell

where @s represents "hold a type s which can be used in the other elements
of the structure".  An example element of this type:

  KI @[Int] (\i s -> (i:s, sum s)) :: KI Int Int

Trying to implement iso as you suggest, we end up with

iso f = KI ?? (\i s -> case f i of ...)

What do we put in the ??.  In fact, it's not possible to find a solution;
consider this:

ki1 :: KI () Int
ki1 = KI @Int (\() s -> (s+1, s))

ki2 :: KI () Int
ki2 = KI @() (\() () -> ((), 0))

f :: Bool -> KI () Int
f x = if x then ki1 else ki2

iso f = KI ?? ??

The problem is that we have multiple possible internal state types!

  -- ryan


> {-
>Couldn't match type `s0' with `s'
>  because type variable `s' would escape its scope
>This (rigid, skolem) type variable is bound by
>  a pattern with constructor
>Kl :: forall i o s. (i -> s -> (s, o)) -> Kl i o,
>  in a lambda abstraction
>The following variables have types that mention s0
>  s :: s0 (bound at /home/tom/meta/haskell/iso.hs:**11:17)
>In the pattern: Kl kl
>In the expression: \ (Kl kl) -> kl () s
>In the expression: (\ (Kl kl) -> kl () s) (f i)
> -}
>
>
> __**_
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/**mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe