On 9/09/2013 7:09 AM, aditya siram wrote:
Hi all,
I'm working on a FLTK [1] GUI binding [2]. The attraction of FLTK is that
there is an existing binding on hackage:
"hs-fltk library: Binding to GUI library FLTK"
which I understand is quite serviceable. Perhaps effort could be
directed on ma
I'm interested in resurrecting the idl generator from lambada:
http://www.dcs.gla.ac.uk/mail-www/haskell/msg02391.html
is the code out there in anyone's attic?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/lis
I am unable to find a copy of the following paper:
Andrew Partridge, David Wright:
Predictive parser combinators need four values to report errors.
Journal of Functional Programming 6(2): 355-364, 1996
does any one have a copy of, that they could send me ?
__
On Wed, Feb 29, 2012 at 9:27 PM, Ras Far wrote:
Hello,
I bit premature perhaps but I wanted to post it on a leap day...
http://fremissant.net/freesect
Thanks for eyebloom on #haskell for motivating me to finally implement
an old idea. Thanks to the rest on #haskell for doing their best to
On 21/01/2012 5:45 AM, Ryan Ingram wrote:
Has anyone played with Idris (http://idris-lang.org/) at all? It looks
interesting, and I'd love to play with it, but unfortunately I only have
windows machines up and running at the moment and the documentation seems
to imply it only builds on unixy sys
"This bill cannot be fixed; it must be killed." - The EFF
yes the act is pernicious, and may cause the wholesale relocation of
content out of the US, to friendlier places like China, perhaps!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.o
It occurs to me that c2hs (or more appropriately the gtk2hsc2hs fork) is
intended to solve this problem; have you looked into it?
hdirect falls into this category as well
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.o
I can't comment on using ghci debugger to observe evaluation. I have in
the past used hood (http://hackage.haskell.org/package/hood) and found
it both convenient and useful when trying to observe evaluation order.
On 2/11/2011 7:00 AM, Captain Freako wrote:
Hi John,
I'm trying to use the G
On 1/11/2011 1:35 AM, Captain Freako wrote:
you need to study ArrowLoop and understand that. In the code
rec (y,s')<- arr f -< (x,s)
s<- delay s0 -< s'
the state is 'captured' in the recursive binding. i.e. just like in real
circuits the output state "s" is threaded back as an input.
T
On 21/10/2011 3:00 AM, David Barbour wrote:
the f in (Automaton f) is a pure funtion runAuto is deconstructing the
arrow by pattern matching then applying the function to the input to
obtain the result and the continuation.
i.e. runAuto takes an arrow and applies it to a value.
On Thu, Oct
ur not doing any composition as
such then lifting your functions into the "arrows" is not buying you much.
John Lask wrote:
This is literate code. It expounds on your initial question and provides
two solutions based either on the StateArrow or Automaton
(Remainder omitted.)
John,
T
> {-# LANGUAGE Arrows #-}
This is literate code. It expounds on your initial question and provides
two solutions based either on the StateArrow or Automaton
> module Test where
> import Data.List ( mapAccumL )
> import Control.Arrow
> import Control.Arrow.Operations
> import Control.Arrow.T
your function corresponds with Control.Arrow.Transformer.Automaton. If
you frame your function is such most of your plumbing is taken care of.
http://hackage.haskell.org/packages/archive/arrows/0.4.1.2/doc/html/Control-Arrow-Transformer-Automaton.html
On 18/10/2011 1:46 PM, Captain Freako wr
On 6/06/2011 3:58 AM, Tom Hawkins wrote:
Another goal of the project is to generate 2D prints from 3D models.
Any idea how hard is this going to be? Basically it needs to identify
features (holes, edges, etc), then project these features to an
orthographic plane, alone with associated dimension
On 19/05/2011 10:31 PM, Heinrich Apfelmus wrote:
my comments for what their worth:
(1) wx and ghci: I successfully run wx in ghci (albeit) on windows. I
take an alternative path to that proscribed by the current build process
- I think principally so that I am able to run it in ghci, although
On 18/05/2011 2:02 PM, Ville Tirronen wrote:
Hello,
I have successfully* built HOpenCV on windows with openCV 2.0 on windows
(XP).
* by successfully, I mean compiled and linked, library and test.hs. The
test did give
me an error:
test-hopencv.exe: user error (Failed to create camera)
whic
On 26/01/2011 1:52 PM, Ivan Lazar Miljenovic wrote:
In which case, why not ask the author(s) directly rather than blindly
asking the mailing list?
others, such as I, may be interested in the answer.
___
Haskell-Cafe mailing list
Haskell-Cafe@haske
I have noticed that on my windows box and ghc 6.12.3 I get the return
list for System.Direcotry.getDirectoryContents in reverse sorted order.
This is a change from previous observed behavior and I would consider it
a bug. I would like to verify that it is not just me.
_
see http://okmij.org/ftp/continuations/Continuations.html, "Zipper-based
file server/OS", aka ZFS
where Oleg addresses concurrent operations on a shared data structure
with multiple mutable cursors implemented via delimited continuations
with varying isolation levels ...
your issues are
On Thu, Nov 11, 2010 at 8:16 PM, John Lask wrote:
consider "length" ...
I have records with the attribute length, length can be given as an Int,
Double, Float or maybe as a constructed type "Length", length's use as a
record selector would also clash with List.length
On 12/11/2010, at 2:16 PM, John Lask wrote:
On 12/11/2010 9:22 AM, Richard O'Keefe wrote:
I'm afraid it's not a *convincing* use case.
It's not convincing because here "owner" *means different things*.
consider "length" ...
I have records with t
On 12/11/2010 9:22 AM, Richard O'Keefe wrote:
On 12/11/2010, at 2:17 AM, Michael Snoyman wrote:
So why would you ever need to reuse the same field name in the same
module?
data PetOwner
data FurnitureOwner
data Cat = Cat { owner :: PetOwner }
data Chair = Chair { owner :: FurnitureOwner }
J
>
> If the outcome of this discussion is a clamour for better records
> instead of TDNR, then that would certainly make me happy.
>
> Regards,
> Malcolm
well I certainly am clamouring for better records.
This motivated my original reply this post. The trouble is, what
constitutes better record
On 11/11/2010 5:21 PM, Ketil Malde wrote:
"Richard O'Keefe" writes:
it is often desirable to have the same field names
for many records in the same module.
very much so, this is currently possible, with the restriction that
the field names must have the same type modulo the record it is
s
On 2/11/2010 9:05 PM, Steffen Schuldenzucker wrote:
On 11/02/2010 10:40 AM, Yves Parès wrote:
Because he would have either to recompile the whole program or to use
things like hint, both implying that GHC must be installed on the user
side (600Mo+ for GHC 6.12.3)
Isn't there a way to use some s
I am not that familiar with LLVM, if anything it complicates matters,
rather than making things easier.
"The llvm-ld program has limited support for native code generation,
when using the -native or -native-cbe options. Native code generation is
performed by converting the linked bitcode into
On 20/08/2010 1:35 PM, Jason Dagit wrote:
fairly easy .. you might want to check out the following tutorial ...
http://www.crsr.net/Programming_Languages/SoftwareTools/ch5.html
he implements a basic grep tool, you might then want to check out one of
the regex packages as a basis for your impleme
On 18/08/2010 12:20 PM, Stephen Sinclair wrote:
you could script in haskell by embedding hugs. Hugs exe + base lib ~ 1MB.
On Tue, Aug 17, 2010 at 6:05 AM, Hemanth Kapila wrote:
Hi,
Can some one please give me a suggestion on the best choice for an embedded
scripting Language for a haskell app
On 20/06/2010 6:32 PM, Alexander Solla wrote:
in your example c will not be in scope in the expression (let b = c >>=
return . f) - that's the purpose of the recursive do construct (mdo, now
"do .. rec ..")
jvl
On Jun 20, 2010, at 6:24 PM, Alexander Solla wrote:
do a <- getChar
let b = c
Whilst I have nothing against the change in syntax for recursive do aka
http://old.nabble.com/Update-on-GHC-6.12.1-td26103595.html
Instead of writing
mdo
a <- getChar
b <- f c
c <- g b
putChar c
return b
you would write
do
a <- getChar
rec { b <- f c
perhaps the inblobs editor may be of some interest
http://haskell.di.uminho.pt/~jmvilaca/INblobs/
allows the editing of interaction nets (also available on hackage)
Andrew Coppin schrieb:
I'm looking at a project which involves a GUI where you can insert
components and wire up connections be
on the topic of llvm,
is anybody using llvm binding on windows ? The official llvm windows
distro does not have a precompiled library which is required for the
llvm bindings ?
jvl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.has
As I said, it is very unix centric. The backend methods rely upon file
descriptors which in the windows world are specific to the C rts. It is
the backend that requires the abstraction from os specific
structures/handling.
The event library has a pluggable interface, with multiple backends, a
Re event library and merge into haskell base: has any thought gone into
the "windows" version of the library. Last I looked it was very unix
centric - the windows api is very different. I believe it will require
major rework to abstract the commonalities and deal efficiently with the
difference
it is easier if you use msys
then in msys window, run ghc setup configure
after that you can run ghc setup build etc in normal dos window without
further recourse to msys
Neil Mitchell wrote:
Hi,
I managed this with the following sequence of commands:
http://www.haskell.org/pipermail/librar
you could have a look at these ...
bjpop-ray - search on web
hray - http://users.elis.ugent.be/~kehoste/Haskell/HRay/
Hello cafe,
While I was studying for my computer graphics test I have tomorrow I
realized that maybe some of the major problems I've read so far about
Radiosity Rendering Al
maybe this helps ...
see http://www.cs.chalmers.se/~aarne/GF/
I quote from the web site: GF is
"a categorial grammar formalism, like ACG, CCG, but different and
equipped with different tools"
it compiles with at least GHC 6.8.2
Is Parsec capable of parsing a mildly context sensitive language
I think it would be a usefull addition to the haskell windows tool
chain, and help facilitate the creation of bindings to libraries on
windows where no appropriate import library exists.
I am sure if you put it "out there" in whatever form, someone will find
a use for it and perhaps build u
I don't know whether this will help you but I just downloaded an built
the haskell portaudio package ... (I had a windows msvc build of
portaudio dll already) the process I used ... ghc 6.10.4, portaudio-19
make an import lib for ghc from dll:
pexports libpa19.dll > libpa19.def
dlltool --input-
I think there are some misapprehensions here:-
many haskell packages binding to c libraries will compile with ghc
without problems on windows - without cygwin, without mingw/msys system.
Some such packages build "out of the box" on windows, like the zlib
package which contains the c source for
look at: http://www.cs.utah.edu/~hal/SVMseq/
this works but is a little slow and would benefit by being updated to
use the bytestring library.
and generic data clustering ...
http://www.cs.utah.edu/~hal/GDC/
> From: ke...@malde.org
> To: hector...@gmail.com
> Subject: Re: [Haskell-cafe] Mach
link to paper: http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.1.7362
- Original Message -
From: Dmitry Olshansky
To: Haskell cafe
Sent: Friday, August 07, 2009 7:31 PM
Subject: Re: [Haskell-cafe] Haskell2Xml
Like in Keith proposal I need it for working with web-se
the paper:
Scripting XML with Generic Haskell
Frank Atanassow, Dave Clarke and Johan Jeuring
October 14, 2003
describes a translation from XML Schema to Haskell data types (like
dtd2haskell) in generic haskell, I believe that the code for the tool
described may also be available, how hard
I would have thought that a major motivation for the study of haskell,or for
that matter ML, Clean, would be their type systems: statically typed higher
order parametric polymorphism which is certainlly different enough from that
of prolog to warrant study. So from the perspective of type system
Can anyone explain the theoretical reason for this limitation, ie other than
it is a syntactical restriction, what would it take to lift this restriction
?
- Original Message -
From: "Stefan Holdermans"
To: "Petr Pudlak"
Cc:
Sent: Saturday, July 18, 2009 5:25 AM
Subject: Re: [Hask
Is there a way to hide instance definitions when importing a module for
instance
I want to import Data.Monoid but wish to redefine the instance of Monoid for
( a->b)
I don't suppose this is possible?
Specifically, I wish to define a specialised instance of Monoid for
String->Int, but it see
The short anser is...you need to make a ffi call to getCurrentProcessId
unfortunately there is no binding to this function in System.Win32.Process
which is the natural home for it.
Perhaps you could submit a patch for Win32 package, once you have created
the binding the signature for the functi
The issue you are experiencing is the result of ghci not using import
libraries to resolve external symbols. Just a bit of explanation for
reference, which will also help you understand the solution to your problem.
Take for example the function declared as
int myexport(int x){...}
when crea
I need to force a library to be searched for unresolved symbols after all
other libraries have been searched, and I would rather not resort to
constructing the linker command line directly. Is there a way to do this?
i.e. I want for example -lfoo to appear after all other haskell libraries
and
on the other hand a function to release pool memory to the OS down to the
current active level should (I hope) be easily implementable, and quickly
incorporated into application where required, whereas arriving at one or
more automatic deallocation policies would most likely require some
analys
for what its worth, I second this suggestion.
- Original Message -
From: "Andrew Coppin"
To:
Sent: Friday, May 08, 2009 6:01 AM
Subject: [Haskell-cafe] GC [Is Haskell a Good Choice for Web Applications?]
Simon Marlow wrote:
http://hackage.haskell.org/trac/ghc/ticket/698
I presum
Well this is interesting. So what you are saying is that if your haskell
application requires a peek memory utilisation of (for example) 1GB, after
the memory intesive computation has completed and the GC has run (assuming
all references have been dropped) the GHC RTS will retain the 1GB allocat
you might like to change the name of the package slightly and thereby avoid
confusion with swish the text indexing engine.
jvl
- Original Message -
From: "Doug Burke"
To: "Vasili I. Galchin"
Cc:
Sent: Friday, May 01, 2009 11:15 PM
Subject: Re: [Haskell-cafe] swish - semantic web in
consider the following types (from the paper:
"Stream Fusion From Lists to Streams to Nothing at All")
data Stream a = forall s. Stream ( s ->(Step a s)) s
data Step a s =
Done
| Yield a s
| Skip s
an instance of this data type is:
stream0 :: Stream ()
stream0 = Stream (\ s -> Yield
Something that has irked me in the past about System.Process is the inability
to obtain an OS system handle from the haskell Process handle. Such a facility
would greatly enhance the interoperabity of c and haskell libraries.
Provision is made (although not standardised) to obtain OS specific
Hi
has anyone had any success in running a recent version of hs-plugins on a
windows platform. I refer to this post to the haskell list in December last
year. The current version of hs-plugins dosn't appear to work either. Same
problem ...
http://www.haskell.org/pipermail/haskell/2007-Decemb
Gunther
Hdirect can be found at: http://www.haskell.org/hdirect/
the Hdirect library was conceived prior to the finalisation of the haskell ffi,
consequently some work would be required to adapt it to the current ffi.
What you want is just the automation library which is only part of the over
Consider the data type:
Foo i o a = ...
we want to declare an instance of Monad and Arrow for Foo without using a
newtype (repackaging).
The effect we want is to be able to construct an expression like:
( f>> g )>>> ( h>> i )
where f, g, h, i :: Foo i o a, for some i o a
it is easy to
who is maintainer of containers package ...
> From: [EMAIL PROTECTED]
> To: [EMAIL PROTECTED]
> Subject: containers-0.1.0.1
> Date: Wed, 12 Mar 2008 23:48:33 +
>
>
>
> containers-0.1.0.1 will not build with ghc-6.6, the lines
>
#include "Typeable.h
Oleg provided the following code to test whether a is a function, this code
will not type check in hugs, due to the overlapping instances in
IsFunction (x->y) f
IsFunction x f
and the functional dependency | a-> b
ERROR "isfunction.lhs":43 - Instances are not consistent with dependencies
*
term.
From: "Claus Reinke" <[EMAIL PROTECTED]>
To: "john lask" <[EMAIL PROTECTED]>
CC:
Subject: Re: [Haskell-cafe] RE: simple function: stack overflow in hugs
vsnonein ghc
Date: Mon, 24 Sep 2007 16:20:42 +0100
afraid not
the given example is too strict, the
einke" <[EMAIL PROTECTED]>
To: "john lask"
<[EMAIL PROTECTED]>,<[EMAIL PROTECTED]>,
Subject: Re: [Haskell-cafe] RE: simple function: stack overflow in hugs vs
nonein ghc
Date: Mon, 24 Sep 2007 13:05:24 +0100
return (repeat 'a') >>= \ x -> print $
I agree with your analysis.
if the following is tried in hugs then ghc you will obtain two different
results..
return (repeat 'a') >>= \ x -> print $ span (const True) x
with hugs you will get a stack error, in ghc it executes in constant space,
i.e. indefinitely. In essenece the above examp
63 matches
Mail list logo