Alfonso Acosta wrote:
It would certainly be difficult map any Haskell type to VHDL, so, by
now we would be content to map enumerate algebraic types (i.e.
algebraic types whose all data constructors have arity zero, e.g.
data Colors = Green | Blue | Red)
Wouldn't it be much simpler to use the s
Hello Henrique,
That license, The Glasgow Haskell Compiler License, available at
http://darcs.haskell.org/ghc-hashedrepo/libraries/haskell-src/LICENSE, reads as
follows:
- license text follows immediately after this line -
The Glasgow Haskell Compiler License
Copyright 2004, The Univer
Thanks a lot for your answer, it was exactly what I was looking for.
Just for the record, based on your solution I can now easily code a
function to check if a Data value belongs to an enumerated algebraic
type (as I defined it in my first mail).
{-# LANGUAGE DeriveDataTypeable, ScopedTypeVariabl
Ryan Ingram wrote:
One point to remember is that structural induction fails to hold on
infinite data structures:
As I understand it, structural induction works even for infinite data
structures if you remember that the base case is always _|_. [1]
Let the initial algebra functor F = const Z
Another way to look at it is that induction is just a way to abbreviate proofs.
Lets say you have a proposition over the natural numbers that may or
may not be true; P(x).
If you can prove P(0), and given P(x) you can prove P(x+1), then for
any given natural number n, you can prove P(n):
P(1)
Hello,
1) Can I set up Haddock to run everytime I do a build?
2) http://hackage.haskell.org/packages/upload.html
- do I have to set up my .cabal in a special way to run "dist"?
- once I checked that my Cabal package is "compliant" on this
page, how do
Am Dienstag, 6. Mai 2008 23:34 schrieb PR Stanley:
> After you grok induction over the naturals, you can start to think
> about structural induction, which is usually what we use in
> programming. They are related, and understanding one will help you
> understand the other (structural induction ac
Hello,
I checked Hoogle for the POSIX data type TimeSpec. Nada. Does anybody
know where the definition is?
Thanks, Vasili
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
After you grok induction over the naturals, you can start to think
about structural induction, which is usually what we use in
programming. They are related, and understanding one will help you
understand the other (structural induction actually made more sense to
me when I was learning, because
On Tue, 2008-05-06 at 09:43 -0400, Mario Blazevic wrote:
> Trevor Elliott wrote:
> > Cabal doesn't pass the --main-is option, I believe because it is
> > specific to GHC. What you could do is add this flag in the ghc-options
> > field of your executable in the cabal file, like this:
> >
> > ghc
Am Dienstag, 6. Mai 2008 22:40 schrieb patrik osgnach:
> Brent Yorgey ha scritto:
> > On Tue, May 6, 2008 at 8:20 AM, patrik osgnach <[EMAIL PROTECTED]>
> >
> > wrote:
> >> Hi. I'm learning haskell but i'm stuck on a generic tree folding
> >> exercise. i must write a function of this type
> >> tree
Am Dienstag, 6. Mai 2008 18:52 schrieb Ross Boylan:
>
> g.hs:11:19:
> Couldn't match expected type `t1 -> GenParser Char () t'
>against inferred type `CharParser st ()'
> In the expression: reserved "\\begin" 1
> In a 'do' expression: reserved "\\begin" 1
> In the expres
Brent Yorgey ha scritto:
On Tue, May 6, 2008 at 8:20 AM, patrik osgnach <[EMAIL PROTECTED]>
wrote:
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise.
i must write a function of this type
treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c
Tree has type
data (
Luke Palmer ha scritto:
On Tue, May 6, 2008 at 6:20 AM, patrik osgnach <[EMAIL PROTECTED]> wrote:
Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i
must write a function of this type
treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c
Tree has type
data
On Tue, 2008-05-06 at 19:46 +0200, Daniel Fischer wrote:
> Am Dienstag, 6. Mai 2008 18:52 schrieb Ross Boylan:
> >
> > Source:
> > import Text.ParserCombinators.Parsec
> > import qualified Text.ParserCombinators.Parsec.Token as P
> > import Text.ParserCombinators.Parsec.Language(haskell)
> > reserv
On Tue, 2008-05-06 at 09:52 -0700, Ross Boylan wrote:
> I kept getting parse failures when I ran my little Parsec TeX snippet on
> a sample code. Seeing that ghc6.8 had debugging, I upgraded to it, only
> to discover that I can't even get the code to compile.
>
> $ ghci
> GHCi, version 6.8.2: htt
Am Dienstag, 6. Mai 2008 18:52 schrieb Ross Boylan:
>
> Source:
> import Text.ParserCombinators.Parsec
> import qualified Text.ParserCombinators.Parsec.Token as P
> import Text.ParserCombinators.Parsec.Language(haskell)
> reserved = P.reserved haskell
> braces = P.braces haskell
>
>
> -- TeX exampl
On Tue, May 6, 2008 at 12:34 PM, Alfonso Acosta
<[EMAIL PROTECTED]> wrote:
| So, the question is. Is there a way to figure out the arity of data
| constructors using Data.Generics ?
| I'm totally new to generics, but (tell me if I'm wrong) it seems that
| Constr doesn't hold any information about
I kept getting parse failures when I ran my little Parsec TeX snippet on
a sample code. Seeing that ghc6.8 had debugging, I upgraded to it, only
to discover that I can't even get the code to compile.
$ ghci
GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help
Loading package base ... lin
Hi all,
I'm writing a Hardware-oriented DSL deep-embedded in Haskell (similar
to Lava, for those familiar with it).
One of the goals of the language is to support polymorphic signals
(i.e. we would like to allow signals to carry values of any type,
including user-defined types)
The embedded c
"Luke Palmer" <[EMAIL PROTECTED]> wrote:
> On Tue, May 6, 2008 at 4:53 AM, Achim Schneider <[EMAIL PROTECTED]>
> wrote:
> > PR Stanley <[EMAIL PROTECTED]> wrote:
> >
> > > Hi
> > > I don't know what it is that I'm not getting where mathematical
> > > induction is concerned. This is relevant to
Hello everybody,
I have one question regarding a licensing issue. I am developing a
library to parse and pretty-print the Core Erlang language and it is
heavily based on the modules included in haskell-src.
What I want to know is if I have to reproduce all of the LICENSE file
included in that pac
After you grok induction over the naturals, you can start to think
about structural induction, which is usually what we use in
programming. They are related, and understanding one will help you
understand the other (structural induction actually made more sense to
me when I was learning, because I
On Tue, May 6, 2008 at 8:20 AM, patrik osgnach <[EMAIL PROTECTED]>
wrote:
> Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise.
> i must write a function of this type
> treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c
> Tree has type
> data (Eq a,Show a)=>Tree
On Tue, May 6, 2008 at 5:34 AM, PR Stanley <[EMAIL PROTECTED]> wrote:
> Hi
> I don't know what it is that I'm not getting where mathematical induction
> is concerned. This is relevant to Haskell so I wonder if any of you gents
> could explain in unambiguous terms the concept please.
> The wikipedi
On Tue, May 6, 2008 at 4:53 AM, Achim Schneider <[EMAIL PROTECTED]> wrote:
> PR Stanley <[EMAIL PROTECTED]> wrote:
>
> > Hi
> > I don't know what it is that I'm not getting where mathematical
> > induction is concerned. This is relevant to Haskell so I wonder if
> > any of you gents could expla
Dan Doel asked me to roll category-extras into my nascent comonad
transformer library, and the result is category-extras 0.44.2!
So since Dan's release a couple of weeks ago (
http://www.haskell.org/pipermail/haskell-cafe/2008-April/042240.html) we
have added:
* Comonad Transformers. Context/Con
On Tue, May 6, 2008 at 6:20 AM, patrik osgnach <[EMAIL PROTECTED]> wrote:
> Hi. I'm learning haskell but i'm stuck on a generic tree folding exercise. i
> must write a function of this type
> treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c
> Tree has type
> data (Eq a,Show a)=>Tr
On 2008 May 6, at 8:37, PR Stanley wrote:
Thus, in traditional logic, if you induce "all apples are red",
simple
observation of a single non-red apple quickly reduces your result to
"at least one apple is not red on one side, all others may be red",
i.e, you can't deduce "all apples are red"
On Tue, May 6, 2008 at 2:50 AM, apfelmus <[EMAIL PROTECTED]> wrote:
> Concerning the folklore that seq destroys the monad laws, I would like
> to remark that as long as we don't apply seq to arguments that are
> functions, everything is fine. When seq is applied to functions,
> already si
Trevor Elliott wrote:
On Mon, 05 May 2008 13:37:12 -0400
Mario Blazevic <[EMAIL PROTECTED]> wrote:
Trevor Elliott wrote:
Hi Mario,
Is the name of the module within the Shell.hs file Main? If not,
that could be your problem.
You may be right, the module's name is Shell, not Main. GHC
PR Stanley <[EMAIL PROTECTED]> wrote:
>
> > > Hi
> > > I don't know what it is that I'm not getting where mathematical
> > > induction is concerned. This is relevant to Haskell so I wonder if
> > > any of you gents could explain in unambiguous terms the concept
> > > please. The wikipedia article
Am Dienstag, 6. Mai 2008 11:34 schrieb PR Stanley:
> Hi
> I don't know what it is that I'm not getting where mathematical
> induction is concerned. This is relevant to Haskell so I wonder if
> any of you gents could explain in unambiguous terms the concept please.
> The wikipedia article offers per
On Tue, May 06, 2008 at 01:04:28PM +0100, Matthew Sackman wrote:
> I'm pleased to announce the general availability of Session Types for
> Haskell, version 2008.5.2. It is available from my website[0],
> Hackage[1][2] and I've just updated the online tutorial[3] to take into
> account the recent ch
> Hi
> I don't know what it is that I'm not getting where mathematical
> induction is concerned. This is relevant to Haskell so I wonder if
> any of you gents could explain in unambiguous terms the concept
> please. The wikipedia article offers perhaps the least obfuscated
> definition I've foun
Hi. I'm learning haskell but i'm stuck on a generic tree folding
exercise. i must write a function of this type
treefoldr::(Eq a,Show a)=>(a->b->c)->c->(c->b->b)->b->Tree a->c
Tree has type
data (Eq a,Show a)=>Tree a=Void | Node a [Tree a] deriving (Eq,Show)
as an example treefoldr (:) [] (++) []
Howdy,
I'm pleased to announce the general availability of Session Types for
Haskell, version 2008.5.2. It is available from my website[0],
Hackage[1][2] and I've just updated the online tutorial[3] to take into
account the recent changes and new features.
[0] http://wellquite.org/non-blog/sessio
PR Stanley <[EMAIL PROTECTED]> wrote:
> Hi
> I don't know what it is that I'm not getting where mathematical
> induction is concerned. This is relevant to Haskell so I wonder if
> any of you gents could explain in unambiguous terms the concept
> please. The wikipedia article offers perhaps the l
Hi
I don't know what it is that I'm not getting where mathematical
induction is concerned. This is relevant to Haskell so I wonder if
any of you gents could explain in unambiguous terms the concept please.
The wikipedia article offers perhaps the least obfuscated definition
I've found so far bu
Hi Mads,
I think there may a bit of problem with the approach you suggest: as
the type returned by the query is computed by the SQL server (if I
understand you correctly), it's very hard to do anything with the
result of the query - the Haskell compiler has no idea what type the
result has, so y
Iavor Diatchki wrote:
apfelmus wrote:
According to the monad law
f >>= return = f
every (>>=) ought to be strict in its first argument, so it indeed
seems that the implementation given in the documentation is wrong.
From the monad law we can conclude only that "(>>= return)" is
strict, not
41 matches
Mail list logo