Mark P Jones wrote:
Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range"
functional dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c ->
On Thu, Apr 17, 2008 at 2:09 AM, Graham Fawcett <[EMAIL PROTECTED]>
wrote:
> I notice in the source for GHC.Handle that certain functions (e.g.
> fdToHandle_stat) are in the export list, but are not actually exported
> (at least, it seems you cannot import them). What mechanism causes
> these func
Hi all,
i'm having some trouble 'getting' functional dependencies in the Haskell
context (although my understanding of them in the context of relational
database theory isn't that great either). Could someone please point me
to an introduction / tutorial in this regard?
Thanks!
Alexis.
___
Martin Sulzmann wrote:
We're also looking for (practical) examples of "multi-range" functional
dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a
Ariel,
In response to your comment, since there was
apparently no section devoted to pitfalls of iterating
over lists, I have added the section "1.4 Iterating
Over a List" in the following HaskellWiki page; viz:
Common Misunderstandings - HaskellWiki
http://www.haskell.org/haskellwiki/Common_Misu
Ariel,
Check out the following HaskellWiki pages:
Common Misunderstandings - HaskellWiki
http://www.haskell.org/haskellwiki/Common_Misunderstandings
Things to avoid - HaskellWiki
http://www.haskell.org/haskellwiki/Things_to_avoid
Hope these help
Benjamin L. Russell
--- "Ariel J. Birnbaum"
minor correction:
test = and [empty, empty]
On 4/16/08, Ryan Ingram <[EMAIL PROTECTED]> wrote:
> You probably want to look at this:
> http://wadler.blogspot.com/2008/02/data-types-la-carte.html
> which refers to a paper about this exact problem.
>
> The main types you want are:
> newtype Fix
You probably want to look at this:
http://wadler.blogspot.com/2008/02/data-types-la-carte.html
which refers to a paper about this exact problem.
The main types you want are:
newtype Fix a = In { out :: a (Fix a) }
data (f :+: g) x = Inl (f x) | Inr (g x)
Yes, you end up with a ton of con
perhaps
haskell:
foreign export "foo_func" foo :: Int -> IO Int
-- I forget the rest of the syntax here
C++:
extern "C" {
int foo_func(int i);
}
int some_cplusplus_function() {
int bat = 3;
int blah = foo_func(bat);
return blah;
}
Is that all you need to do?
Miguel Lordelo wrote:
Hi
One question is whether the program is statically or dynamically linked,
and if the latter, whether it is possible (as it is in many Unices) to
slide your own open(2) definition in between the program and the system
library. If it is, it's possible to slide in something that fakes
/dev/stdin.
__
I notice in the source for GHC.Handle that certain functions (e.g.
fdToHandle_stat) are in the export list, but are not actually exported
(at least, it seems you cannot import them). What mechanism causes
these functions to be "hidden", and are they still accessible in some
way?
Graham
___
I think I was the one confused.
I guess I was (falsely) thinking that both
C Int Char T
C Char Int T
could both be instances of class C a b c | c -> a, c -> b but only one
could be an instance of C a b c | c -> a b.
Sorry for adding noise to the discussion.
Ryan Ingram wrote:
I'm sti
On Wednesday 16 April 2008 6:16:56 pm Brandon S. Allbery KF8NH wrote:
> On Apr 16, 2008, at 17:30 , John Goerzen wrote:
> > On Wed April 16 2008 3:54:45 pm Galchin, Vasili wrote:
> >>I already found this link. Thanks in any case. I want to
> >> O_CREATE a
> >> file, i.e. do a openFd creating a
Here's the setup:
I have a series of problems that use various logical connectives. The
problem is that they're not all the same. So instead of creating one
giant datatype (or duplicating much code), I'd like to assemble them
like toy blocks.
I've boiled down an example here:
data LogicalConnec
On Apr 16, 2008, at 17:30 , John Goerzen wrote:
On Wed April 16 2008 3:54:45 pm Galchin, Vasili wrote:
I already found this link. Thanks in any case. I want to
O_CREATE a
file, i.e. do a openFd creating a new file. O_CREATE should be the
FileMode, but I don't see in the link below.
Indee
Donn Cave wrote:
I have run into this problem, with Network.Socket (socket). If I
remember right,
ktrace showed me what was happening. This isn't my favorite thing about
Haskell.
Is there even a means provided to set it back to blocking?
There isn't a way right now to open a file using a b
I'm still confused about this point:
On 4/16/08, Dan Weston <[EMAIL PROTECTED]> wrote:
> > > class C a b c | c -> a b
> > >
> > > Notice that there are multiple (two) parameters in the range of the FD.
> > >
> > > It's tempting to convert the above to
> > >
> > > class C a b c | c -> a, c -> b
On Wed, Apr 16, 2008 at 5:30 PM, John Goerzen <[EMAIL PROTECTED]> wrote:
> On Wed April 16 2008 3:54:45 pm Galchin, Vasili wrote:
> > hi Antoine,
> >
> >I already found this link. Thanks in any case. I want to O_CREATE a
> > file, i.e. do a openFd creating a new file. O_CREATE should be the
On Wed April 16 2008 3:54:45 pm Galchin, Vasili wrote:
> hi Antoine,
>
>I already found this link. Thanks in any case. I want to O_CREATE a
> file, i.e. do a openFd creating a new file. O_CREATE should be the
> FileMode, but I don't see in the link below.
Indeed. It seems there is no way to p
Hi Vasili,
>I already found this link. Thanks in any case. I want to O_CREATE a file,
> i.e. do a openFd creating a new file. O_CREATE should be the FileMode, but I
> don't see in the link below.
What do you want to do beyond writeFile/openFile/readFile? If you can,
its better to use the stan
hi Antoine,
I already found this link. Thanks in any case. I want to O_CREATE a file,
i.e. do a openFd creating a new file. O_CREATE should be the FileMode, but I
don't see in the link below.
Thanks, Vasili
On Wed, Apr 16, 2008 at 1:46 PM, Antoine Latter <[EMAIL PROTECTED]> wrote:
> 2008/4/1
Hi folks, I'm a newbie, so please forgive any terminological mistakes.
I've been using Shim in Emacs with great success, but there's one
issue I've encountered, and I don't know if it's configuration problem
or something fundamental. Consider a module 'App' and submodules
'App.Front' and 'App.Back
> That's exactly what I was thinking about, but your hanoi_shower only
> handles list of exactly one action, but you have to handle longer lists,
> too. This could be done with explicit recursion
This seems to be a common pitfall for Haskell newcomers: mistaking
a single-element list pattern (such
On Apr 16, 2008, at 14:08 , Marc Weber wrote:
src/System/IO/Binary.hs:266:8:
Illegal signature in pattern: ForeignPtr CChar
Use -XPatternSignatures to permit it
Hackage confirms this build failure:
http://hackage.haskell.org/packages/archive/MissingH/1.0.1/logs/
failure/ghc-6.8
S
Hi
> I tried d to use Hoogle to find openFd's signature and more
> importantly FileMode.
Hoogle does not search the Posix library, because in general people
should steer clear of it - otherwise I won't be able to run your
programs :-) - The next version of Hoogle will permit selecting to
se
2008/4/16 Galchin, Vasili <[EMAIL PROTECTED]>:
> Hello,
>
> I tried d to use Hoogle to find openFd's signature and more
> importantly FileMode. I found FileMode which is a type synonym with CMode.
> I don't understand what are the "values" for FileMode (so I can call
> openFd). ??
Values of
Hello,
I tried d to use Hoogle to find openFd's signature and more
importantly FileMode. I found FileMode which is a type synonym with CMode.
I don't understand what are the "values" for FileMode (so I can call
openFd). ??
Thanks,
Vasili
___
Has
Denis Bueno wrote:
> I'm using the Data.Graph.Inductive.Query.Dominators library
> (http://haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inductive-Query-Dominators.html)
> with GHC 6.8.2.
> The library is a bit spare on comments, so I may or may not be using
> it correctly.
>
[snip]
>
On Wed April 16 2008 1:08:08 pm Marc Weber wrote:
> > src/System/IO/Binary.hs:266:8:
> > Illegal signature in pattern: ForeignPtr CChar
> > Use -XPatternSignatures to permit it
> >
> > Hackage confirms this build failure:
> > http://hackage.haskell.org/packages/archive/MissingH/1.0.1/lo
On Wed April 16 2008 12:20:37 pm Brandon S. Allbery KF8NH wrote:
> On Apr 16, 2008, at 11:16 , John Goerzen wrote:
> > On 2008-04-15, Joe Buehler <[EMAIL PROTECTED]> wrote:
> >> John Goerzen wrote:
> >>> So I have a need to write data to a POSIX named pipe (aka FIFO).
> >>> Long
> >>> story involvi
> src/System/IO/Binary.hs:266:8:
> Illegal signature in pattern: ForeignPtr CChar
> Use -XPatternSignatures to permit it
>
> Hackage confirms this build failure:
> http://hackage.haskell.org/packages/archive/MissingH/1.0.1/logs/failure/ghc-6.8
Should not be hard to fix :) just add it
Iavor Diatchki wrote:
Hello,
On Wed, Apr 16, 2008 at 8:06 AM, Martin Sulzmann
<[EMAIL PROTECTED]> wrote:
We're also looking for (practical) examples of "multi-range" functional
dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It
On Apr 16, 2008, at 10:25 AM, Brandon S. Allbery KF8NH wrote:
On Apr 16, 2008, at 13:23 , Miguel Mitrofanov wrote:
You are insulting other Unixes. It works on Mac OS X, for example.
Not just that, but IIRC Linux was late to the party: Solaris got /
dev/fd/ and /dev/stdin before Linux got /
Hello,
On Wed, Apr 16, 2008 at 8:06 AM, Martin Sulzmann
<[EMAIL PROTECTED]> wrote:
> We're also looking for (practical) examples of "multi-range" functional
> dependencies
>
> class C a b c | c -> a b
>
> Notice that there are multiple (two) parameters in the range of the FD.
>
> It's tempting
On Wed, Apr 16, 2008 at 12:02 AM, John Goerzen <[EMAIL PROTECTED]> wrote:
> Hi,
>
> I'm pleased to announce the first release of datapacker.
Your datapacker depends on MissingH 1.0.1 which, although on hackage,
fails to build with GHC 6.8.2. (It may build with earlier versions,
but I haven't tri
On Apr 16, 2008, at 13:23 , Miguel Mitrofanov wrote:
You are insulting other Unixes. It works on Mac OS X, for example.
Not just that, but IIRC Linux was late to the party: Solaris got /
dev/fd/ and /dev/stdin before Linux got /proc/$$/fd/ (which gets
symlinked to /dev/fd/).
--
brandon s
You are insulting other Unixes. It works on Mac OS X, for example.
On 16 Apr 2008, at 19:16, John Goerzen wrote:
On 2008-04-15, Joe Buehler <[EMAIL PROTECTED]> wrote:
John Goerzen wrote:
So I have a need to write data to a POSIX named pipe (aka FIFO).
Long
story involving a command that do
On Apr 16, 2008, at 11:16 , John Goerzen wrote:
On 2008-04-15, Joe Buehler <[EMAIL PROTECTED]> wrote:
John Goerzen wrote:
So I have a need to write data to a POSIX named pipe (aka FIFO).
Long
story involving a command that doesn't have an option to read data
from stdin, but can from a name
magnus:
>On Wed, Apr 16, 2008 at 4:01 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
>
> magnus:
> >Is there such a beast out there?
> >
> >If this were a list on some OO language I'd ask for something that
> created
> >an AST and then offered an API based
On Wed, Apr 16, 2008 at 4:01 PM, Don Stewart <[EMAIL PROTECTED]> wrote:
> magnus:
> >Is there such a beast out there?
> >
> >If this were a list on some OO language I'd ask for something that
> created
> >an AST and then offered an API based around a visitor pattern.
> >
> >The pre
On 2008-04-15, Joe Buehler <[EMAIL PROTECTED]> wrote:
> John Goerzen wrote:
>
>> So I have a need to write data to a POSIX named pipe (aka FIFO). Long
>> story involving a command that doesn't have an option to read data
>> from stdin, but can from a named pipe.
>
> How about /dev/stdin?
Only wor
Hello Martin,
Wednesday, April 16, 2008, 7:06:07 PM, you wrote:
i'm not 100% sure that you'll find there appropriate examples but i
suggest you too look into http://haskell.org/haskellwiki/Library/Streams
where i've used very sophisticated (for me) FDs
> We're also looking for (practical) exampl
On Wed, Apr 16, 2008 at 04:30:27PM +0200, Tom Schrijvers wrote:
> I'm looking for practical examples of non-full functional dependencies
> and would be grateful if anyone could show me some or point to
> applications using them.
>
> A non-full functional dependency is one involves only part of th
We're also looking for (practical) examples of "multi-range" functional
dependencies
class C a b c | c -> a b
Notice that there are multiple (two) parameters in the range of the FD.
It's tempting to convert the above to
class C a b c | c -> a, c -> b
but this yields a weaker (in terms of typ
magnus:
>Is there such a beast out there?
>
>If this were a list on some OO language I'd ask for something that created
>an AST and then offered an API based around a visitor pattern.
>
>The pre-processor (platform specific most likely, but could be cpphs of
>course) would be
ketil:
>
> One of the downsides of a 64-bit environment is the increased size of
> pointers. This means that the cost of a String increases from
> something like 12 bytes per char to something like 24.
>
> I notice BEA uses something called "compressed pointers" to get the
> 64-bit (more registe
write the C wrapper that calls haskell, then link that to your C++ objects
I think what you're really asking is how to call C from C++
-Dan
2008/4/16 Miguel Lordelo <[EMAIL PROTECTED]>:
> Hi all,
>
> Well...somehow I'm a beginner in Haskell. But actually my interest in
> Haskell will increase i
Hello,
I'm looking for practical examples of non-full functional dependencies and
would be grateful if anyone could show me some or point to applications
using them.
A non-full functional dependency is one involves only part of the
parameters of a type class. E.g.
class C a b c | a
Next year, I'm thinking of going overseas (I'm currently in Australia)
to do a PhD. Preferably, I'd like to do something in the area of
computational combinatorics using Haskell. Does anyone know of any
particular unis/supervisors I should be looking at/talking to about
this?
--
Ivan Lazar Milj
On 16 Apr 2008, at 15:14, Miguel Mitrofanov wrote:
Before somebody noticed: I'm wrong.
It's not List monad, but also a "(->) x" monad, also defined in
Control.Monad.
Therefore, "return y" is just "const y". Therefore,
x >>= (return y) = x >>= (const y) = x >> y
Right. It is an interesting
On 16 Apr 2008, at 15:22, Daniel Fischer wrote:
The point is the
instance Monad ((->) a) where
return x = const x
f >>= g = \x -> g (f x) x
which is defined in Control.Monad.Instances...
Thank you. I suspected there was an instance somewhere, and I wanted
to know where it is defined
Am Mittwoch, 16. April 2008 14:56 schrieb Hans Aberg:
> When I load the State module in Hugs, then I can define the function
> f below, but I do not immediately see exactly what function "return"
> returns. Explanation welcome.
>
> For example:
>> f [2..4] [6..9]
>
>[6,7,8,9,6,7,8,9,6,7,8,9
Miguel Mitrofanov wrote:
It has nothing to do with State; it actually works in List monad.
"return y" is just another way of writing "[y]".
Actually, it seems that in this case return is from the ((->) a) monad,
i.e. return=const.
f x y = x >>= return y
= x >>= const y
= (concat
Before somebody noticed: I'm wrong.
It's not List monad, but also a "(->) x" monad, also defined in
Control.Monad.
Therefore, "return y" is just "const y". Therefore,
x >>= (return y) = x >>= (const y) = x >> y
On 16 Apr 2008, at 17:04, Miguel Mitrofanov wrote:
It has nothing to do with St
It has nothing to do with State; it actually works in List monad.
"return y" is just another way of writing "[y]".
You don't need to import Control.Monad.State for this to work; you
only need Control.Monad (which is imported by the former).
On 16 Apr 2008, at 16:56, Hans Aberg wrote:
When I
When I load the State module in Hugs, then I can define the function
f below, but I do not immediately see exactly what function "return"
returns. Explanation welcome.
For example:
> f [2..4] [6..9]
[6,7,8,9,6,7,8,9,6,7,8,9]
That is, it just repeats the second argument as many times as th
On Apr 16, 2008, at 4:45 AM, Ketil Malde wrote:
I notice BEA uses something called "compressed pointers" to get the
64-bit (more registers, etc) benefits without paying the
(cache-thrashing) cost.
But only if you're not *actually* using a 64-bit address space. From
their own documentation:
On 16/04/2008, at 0:53, Galchin, Vasili wrote:
Hello,
I have an Linux executable of my Haskell library and test case.
I see there are several debuggers, e.g. Buddha, Hat, etc. Which
debugger is currently preferred for monadic (imperative) code? Thanks.
Vasili
For debugging IO cod
One of the downsides of a 64-bit environment is the increased size of
pointers. This means that the cost of a String increases from
something like 12 bytes per char to something like 24.
I notice BEA uses something called "compressed pointers" to get the
64-bit (more registers, etc) benefits wit
Hi all,
Well...somehow I'm a beginner in Haskell. But actually my interest in
Haskell will increase if it is possible to call a haskell function in C++.
Something like GreenCard ( http://www.haskell.org/greencard/ ) simplifying
the task of interfacing Haskell programs to external libraries (usuall
Abhay Parvate wrote:
I am not saying that it should claim it as soon as it is unused; all I
am saying that as soon as a priority object becomes unreferenced, it
should be the first choice for collecting in the next collect.
Further I was under the impression (I may be wrong) that it uses a
gene
Thanks, both for the summary and for the link. Will try to go through it.
Regards,
Abhay
On Wed, Apr 16, 2008 at 12:37 PM, Bulat Ziganshin <[EMAIL PROTECTED]>
wrote:
> Hello Abhay,
>
> Wednesday, April 16, 2008, 10:51:07 AM, you wrote:
>
> > I am not saying that it should claim it as soon as it
Hello Abhay,
Wednesday, April 16, 2008, 10:51:07 AM, you wrote:
> I am not saying that it should claim it as soon as it is unused;
> all I am saying that as soon as a priority object becomes
> unreferenced, it should be the first choice for collecting in the next
> collect.
on the GC, all unref
63 matches
Mail list logo