Hi guys,
Yep, we know about this and, I believe, the plan is to add custom rules to
the constraint solver to solve `Typable n` constraints (where n is a
number or symbol). Just for the record, the other design choice was to
add instance `Typeable (n :: Symbol)`, but that conflicted with some of
o are already eligible to work in the US.
-Iavor
On Thu, Jun 27, 2013 at 9:03 AM, Alejandro Serrano Mena
wrote:
> Hello,
> Are there any specific details to consider when applying? For example, is
> living in the US or having a visa required for application?
>
> Thanks in advance.
&
Hello,
Galois is hiring! We're looking for researchers, principal investigators,
and software engineers, including those with expertise in functional
programming, formal methods, computer security, control systems,
informatics, or networking.
For more information, take a look at http://corp.galo
Hello,
I haven't merged the type-nats branch with GHC master recently, so some of
the libraries probably moved forward, which could be the source of the
problem. I'll make sure to fix it over the next couple of days.
-Iavor
On Mon, Feb 25, 2013 at 6:39 AM, Takayuki Muranushi wrote:
> Hi, everyo
Hello Martin,
the change that you propose seems to already be in json-0.7. Perhaps you
just need to 'cabal update' and install the most recent version?
About your other question: I have not used CouchDB but a common mistake is
to mix up strings and bytes. Perhaps the `getDoc` function does not
Hello,
On Sun, Jan 13, 2013 at 12:05 PM, Conal Elliott wrote:
>
>
> so there is really no way for GHC to figure out what is the intended value
>> for `a`.
>>
>
> Indeed. Though I wonder: does the type-checker really need to find a
> binding for `a` in this case, i.e., given the equation `(forall
Hello Conal,
The issue with your example is that it is ambiguous, so GHC can't figure
out how to instantiate the use of `foo`. It might be easier to see why
this is if you write it in this form:
> foo :: (F a ~ b) => b
> foo = ...
Now, we can see that only `b` appears on the RHS of the `=>`, s
Hi,
I think that this is a neat idea that should be explored more! GHC's
parser has a bunch of awkward duplication to handle attaching documentation
to types, and it'd be cool if we could replace it with an actual language
construct.
Happy holidays!
-Iavor
On Wed, Dec 26, 2012 at 3:27 AM, Chri
other stuff, so we really need
someone who's using the library to help.
Thanks!
-Iavor
On Mon, Nov 12, 2012 at 2:06 PM, Iustin Pop wrote:
> On Mon, Nov 12, 2012 at 10:57:25PM +0100, Iustin Pop wrote:
> > On Mon, Nov 12, 2012 at 01:48:23PM -0800, Iavor Diatchki wrote:
> > &
Hi,
the curl binding certainly needs some love---if anyone has the time to fix
it up and maintain it, help would be most appreciated. There is a repo for
it over here: https://github.com/GaloisInc/curl which is the most up-to
date version I know of, but since the last commit there seems to be fro
Hello Arie,
One way to achieve the additional static checking is to use values of type
`Sing (n :: Nat)` in the places where you've used `Integer` (and
parameterize data structures by the `n`). If the code is fully polymorphic
in the `n`, then you can use it with values whose types as not statica
Hello,
I think that getting a certificate is a good idea. I think this could
probably be arranged by the haskell.org committee, which even has a budget
for things like that, I believe. I'm cc-ing Jason, who's on the committee
and might have more input on what's the best way to proceed.
Thanks f
Hello,
Sorry, I made a mistake, the version of 'repeat :: Proxy n -> a -> Vector n
a' won't work either, as Andres noticed, because `Proxy` still won't give
you information about how many times to repeat.
You'd have to use a structured singleton family, where the values are
linked to the types:
d
Hello Paul,
If you don't want to use the class system, you could write `repeat` with a
type like this:
repeat :: Proxy n -> a -> Vector n a
(`Proxy` is the singleton family 'data Proxy n = Proxy`).
You can't really do it with a function of type `a -> Vector n a` because
there is no way for
Hello,
I am pleased to announce the availability of monadLib-3.7.1 on Hackage.
MonadLib is a library intended to help programmers to quickly and easily
construct various monads. The library has support for a wide range of
effects: threading state, read-only variables, collecting output,
except
Hello,
this happens because "head" probably closes the file descriptor after 3
lines, and then the Haskell program tries to write to a closed handle
(i.e., it's stdout is not there anymore). The best thing to do depends on
the program. One fairly simple option would be to handle the exception, and
Hello,
I also completely agree with Bryan's point which is why I usually don't add
upper bounds on the dependencies of the packages that I maintain---I find
that the large majority of updates to libraries tend to be backward
compatible, so being optimistic seems like a good idea.
By the way, some
super
class constraint holds.
-Iavor
On Wed, May 30, 2012 at 11:14 PM, Etienne Laurin wrote:
> 2012/5/31 Iavor Diatchki :
> > Hello,
> >
> > the notion of a functional dependency is well established, and it was
> used
> > well before it was introduced to Haskell (f
Hello,
the notion of a functional dependency is well established, and it was used
well before it was introduced to Haskell (for example, take a look at
http://en.wikipedia.org/wiki/Functional_dependency). So I'd be weary to
redefine it lightly.
Note that placing a functional dependency constraint
Hello,
On Wed, Jul 7, 2010 at 2:14 PM, Simon Peyton-Jones wrote:
> We can’t permit overlap for type families because it is *unsound *to do
> so (ie you can break “well typed programs don’t go wrong”). But if it’s
> unsound for type families, it would not be surprising if it was unsound for
> fun
Hi,
It is quite likely that the error that you are getting with approach 2 is
because when you are constructing the `Combinator` value, there is not
enough type information to figure out how to solve the constraint (and it
sounds like this happens because there is not enough type information to
re
Hello,
The context in your example serves an important purpose: it records the
fact that the behavior of the function may differ depending on which type
it is instantiated with. This is quite different from ordinary
polymorphic functions, such as `const` for example, which work in exactly
the s
Hello,
On Mon, Feb 20, 2012 at 7:03 PM, Johan Tibell wrote:
>
> Looks really nice.
Thanks!
> The hovering behavior is nice, but I'd like to see
> the legend as well. It makes it quicker when you want to get a quick
> overview of what types there are, as the eye can travel back-and-forth
> betw
Hello,
On Tue, Sep 27, 2011 at 8:49 AM, Chris Smith wrote:
> You could calculate the entire range using Rational and then convert
> each individual value after the fact. That doesn't seem like a
> reasonable default, since it has a runtime performance cost. Of course
> you're welcome to do it w
Hi,
that's a bug in GHC---it erroneously accepts polymorphic instances which
violate the FD of a class.
-Iavor
On Fri, Mar 18, 2011 at 7:08 AM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:
> On Friday 18 March 2011 14:40:40, JP Moresmau wrote:
> > Thanks to you all, I think I underst
Hi Lee,
I would also guess that these are probably the implementations of equality
in the given modules.
One way to test this would be to name the equality function explicitly. For
example, something like this:
myEquality x y = ...
instance Eq MyType where (==) = myEquality
Another option would
Hello,
I just noticed that the instances for this example look more readable when
written with two recently proposed Haskell extensions. Perhaps we should
consider implementing these in GHC?
Using chain instances: (http://web.cecs.pdx.edu/~mpj/pubs/instancechains.pdf
)
> instance DeepFlat a b =>
Hi Patrick,
Indeed, you cannot really write proofs in Haskell because it is just
an ordinary (more or less) programming language and not a theorem
prover. (As an aside: you could write "tests", i.e. properties which
may or may not be theorems about your program, and test them on random
data (see Q
Hello,
I think that we should make both changes (make Applicative a
super-class of Monad, and remove the "fail" method from Monad). Code
will break but we can fix it.
By the way, just for reference, the proposal to have a separate
failure class and using it in the "do" notation, is how things us
largely a
matter of taste.
-Iavor
On Thu, Dec 2, 2010 at 11:03 AM, Larry Evans wrote:
> On 12/02/10 11:19, Iavor Diatchki wrote:
>> Hi,
>> Bart Jacobs's book "Categorical Logic and Type Theory" has a
>> categorical description of a system with dependent types (
Hi,
Bart Jacobs's book "Categorical Logic and Type Theory" has a
categorical description of a system with dependent types (among
others). The book is fairly advanced but it has lots of details about
the constructions.
Hope this helps,
-Iavor
On Thu, Dec 2, 2010 at 8:18 AM, wrote:
> On Thu, 2 De
Hi,
It sounds like your "use of `ioctl'' at topIO.hs:21:35-60" is passing
an "Int" as the 3rd argument to "ioctl", when your instance
declaration states that this argument should be a "C'winsize".
-Iavor
On Wed, Nov 24, 2010 at 11:27 PM, Magicloud Magiclouds
wrote:
> Hi,
> In System.Posix.IOCtl,
Hi,
actually this idea generalizes quite nicely. Details and examples are
available in Section 3 of "Language and Program Design for Functional
Dependencies", available at
http://web.cecs.pdx.edu/~mpj/pubs/fundeps-design.html
-Iavor
On Mon, Sep 6, 2010 at 3:58 PM, Wolfgang Jeltsch
wrote:
> Am M
Hi,
according to this page:
http://hackage.haskell.org/package/pango-0.11.0
pango should work with cairo 0.11.0 (or any other 0.11.* version)
So it seems that the problem is that cabal tried to use pango-0.11.1,
and I am guessing that it does not backtrack and try an older version
if a build fails
The changelog feature would be very useful---dumping repository
history is no substitute for it because it is too low level (contains
too much noise). Generally, I would expect that whoever makes the
release of a piece of software should be in charge of writing a
summary of what's new since the la
Hi,
When using monadLib, I use newtype deriving to get the Functor,
Applicative, and Monad instances for my custom newtyped monad. Those
work just fine, and there is nothing unsafe about them.
For a custom monad, I usually don't derive MonadLib's effect classes
directly. Instead, I tend to defin
Hi,
it seems that this was already fixed in the repo, I've put a new
version (0.4.4) on hackage. Thanks, again, for spotting this!
-Iavor
On Wed, May 12, 2010 at 1:24 PM, Daniel Fischer
wrote:
> On Wednesday 12 May 2010 21:53:41, Martin Hilbig wrote:
>> hi,
>>
>> since i got no answer from the m
Hi,
I think it was probably I who wrote this, so I'll take the blame :-)
It seems like a genuine bug, where we are not checking for strings
that are not terminated. Thanks for spotting it, and also for the
patch! I'll try to update the package soon.
-Iavor
On Wed, May 12, 2010 at 12:53 PM, Marti
gt; IO a -> IO a
scopedSetMask_ m io = scopedSetMask m $ \_ ->
io
-- Simon's mask:
mask :: ((IO a -> IO a) -> IO b) -> IO b
mask f = scopedSetMask MaskedInterruptible $ \m ->
f (scopedSetMask_ m)
-Iavor
On Sa
Hello,
It seems that rank-2 types are sufficient to make the more polymorphic types:
{-# LANGUAGE Rank2Types #-}
import Control.Exception
data Mask = Mask (forall a. IO a -> IO a)
mask :: (Mask -> IO a) -> IO a
mask io = do
b <- blocked
if b
Hi everyone,
thanks for your efforts to improve the site! To be honest, I don't
really like the current design, so here are some suggestions that
might help:
* I find the color scheme a bit bleak; I'd prefer something more colorful.
* Some graphics might improve the overall style.
* We need to
Hi Mark,
On Sun, Jan 17, 2010 at 5:30 AM, Mark Spezzano
wrote:
> Question: Am I going about this the right way? I want to put together lots of
> "data" types like Verb and Noun etc so that I can build a kind of "BNF
> grammar".
Your basic idea to use a datatype is a good one. You just need to
Hi,
I usually refer to this structure as a RingBuffer, just an idea. If
you have the time, I would add rough complexity estimates to the
documentation for the different functions. Thanks for your work!
Happy new year,
Iavor
On Thu, Dec 31, 2009 at 1:13 PM, John Van Enk wrote:
> I've decided to
Hi,
Not everyone in the community is keen on replacing functional
dependencies with type families. My advice would be to use whichever
language construct seems more suitable to your problem and disregard
the occasional posts by people claiming that functional dependencies
are obsolete or deprecate
Hi everyone,
While you are discussing performance of parsing combinator libraries,
I though I'd mention "parsimony", available from Hackage. It has as
good performance as parsec v2 but it also has support for different
buffer types (e.g., byte strings, including support for utf8 decoding,
etc) whi
Hi
On Tue, Dec 1, 2009 at 11:02 AM, Gour wrote:
> Iavor> In general, I don't think that having two similar libraries is a
> Iavor> huge problem. I tend to do this kind of hacking for fun, and I
> Iavor> really do not enjoy the competition that is being encouraged
> Iavor> when we try to select "
Hi,
I work with Trevor on the other Clutter binding. We did exchange a
few messages with Matt, but we were not sure how to combine the two
libraries because our approaches to writing the binding were a bit
different. In general, I don't think that having two similar
libraries is a huge problem.
Hi,
On Tue, Oct 6, 2009 at 2:37 AM, Henning Thielemann
wrote:
> Numeric literals are treated as Integer or Rational, and are then converted
> with the function fromInteger or fromRational, respectively, to the required
> type. Whatever fromInteger function is in scope, will be used. If
> fromInte
I agree with Grzegorz. Perhaps we should file a bug-report, if there
isn't one already?
-Iavor
2009/9/24 Grzegorz Chrupała :
> 2009/9/23 Bulat Ziganshin :
>> Hello Grzegorz,
>>
>> Wednesday, September 23, 2009, 7:19:59 PM, you wrote:
>>
>>> This seems like a bug in the implementation of writeArra
(argh, sorry about that, I pressed something and gmail sent my
unfinished email!)
On Sun, Sep 13, 2009 at 9:54 PM, Iavor Diatchki
wrote:
> Hi,
> It seems that the problem is the site is using GHC 6.6.1, and
> something was broken at the time (I have not looked into what that
> is)
Hi,
It seems that the problem is the site is using GHC 6.6.1, and
something was broken at the time (I have not looked into what that
is).
Here are the outputs that I get for the little example on the site
that you posted:
GHC 6.10.3 and C++:
On Sun, Sep 13, 2009 at 10:15 AM, Diego Souza wrot
Hello,
On Tue, Aug 4, 2009 at 2:50 PM, Neil Mitchell wrote:
> Hi
>
>> Some good reasons for having a separate interface are: they can be
>> human-readable and human-writable (ghc's do not fulfill this criterion);
>> they can be used to bootstrap mutually recursive modules in the absence of
>> any
Hello,
you may also find the package "pretty-show"
(http://hackage.haskell.org/package/pretty-show) useful. It contains
code to convert automatically derived instances of "Show" into an
explicit data structure, which you can then manipulate (e.g., by
adding the extra field), and then render back t
Hello,
I think that Even refers to an example like this:
module A where
data A = A { a :: Int }
The following works:
{-# LANGUAGE NamedFieldPuns #-}
module B where
import A
f (A { a }) = a
However, if we import "A" qualified, then punning does not seem to work:
{-# LANGUAGE NamedFieldP
Hello,
I do not think that we should remove the current record/named fields
syntax, at least for the moment. I use it a lot, and I do not want to
add extra pragmas or "extensions" to my cabal file. In fact, one of
the purposes of Haskell', the way I understand it, is exactly to just
choose a stab
Hi,
you may also want to look at:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xml
It knows about namespaces and, also, it's parser is lazy.
-Iavor
On Mon, Jun 8, 2009 at 11:39 AM, John Millikin wrote:
> I'm trying to convert an XML document, incrementally, into a sequence
> of XML
r
On Mon, Jun 8, 2009 at 4:48 PM, Iavor Diatchki wrote:
> Hi,
> As Thomas pointed out, it is not clear if this is a bug, or if there
> is something confused between the different versions of Windows and
> MinGW (or I just did something wrong) but I'll make a ticket so that
> we
py to try out fixes/ideas on my Windows machine as I think
that it is important that we have as good support for Windows as we do
on the various Unix-like systems.
-Iavor
On Mon, Jun 8, 2009 at 1:23 PM, Bryan O'Sullivan wrote:
> On Sun, Jun 7, 2009 at 5:04 PM, Iavor Diatchki
> wrote:
Hi,
Interesting. In that case, does anyone have any ideas about the
linker errors?
-Iavor
On Mon, Jun 8, 2009 at 12:42 AM, Thomas ten Cate wrote:
> On Mon, Jun 8, 2009 at 02:04, Iavor Diatchki wrote:
>> Hello,
>> Here is an update, in case anyone else runs into the same pr
neral, it seems a bad idea that the same version of the network
package exhibits different APIs, depending on the configuration of the
underlying system.
-Iavor
On Sat, Jun 6, 2009 at 9:43 PM, Iavor Diatchki wrote:
> Hi,
> I have been trying to build the package "network"
Hi,
I have been trying to build the package "network" from hackage
(version 2.2.1.3) on Windows Vista, and I could really use some help.
Building on the command line, or under cygwin completely failed
(command line due to cabal not being able to execute
something---possibly configure---although it
Hi Conor,
As someone pointed out, CGI is one way to go.
Another option is to write a small Haskell web server. This path is
better if you have an app that needs to keep state, ans uses the
browser mostly as a GUI.
I have just made a package that should make doing this fairly easy. I
have not uplo
Hi,
Using a type class in the way Wren suggests seems to be the right way
to do this in Haskell, as it is at the moment. I don't think that
this an inappropriate use of type classes at all---in fact, it is
exactly what type classes were designed to do (i.e., allow you to
reuse the same name at dif
Hello,
What is the preferred way to install a cabal package so that it works
with winhugs? When I tried "cabal install --user --hugs" I got an
error that it could not find "hugsffi". I managed to get things
working by manually downloading the package, and extracting the
appropriate source directo
Hi,
On Fri, Apr 10, 2009 at 1:28 AM, Bas van Dijk wrote:
> Now I'm wondering if the derive_* functions can be overloaded using
> something like this. Note that the following doesn't typecheck:
>
>
>
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE
Hi,
You can do things like that for "new" monads that are isomorphic to
existing ones. Take a look at the MonadLib.Derive package from
MonadLib
(http://hackage.haskell.org/packages/archive/monadLib/3.5.2/doc/html/MonadLib-Derive.html).
More specifically, the functions "derive_return" and "derive
Hi,
The linking problem might be due to a bug in the cabal file: if you
have modules that are not exposed, you still need to list them in the
"other-modules" section.
-Iavor
On Thu, Apr 2, 2009 at 10:01 AM, Gleb Alexeyev wrote:
> Don Stewart wrote:
>>
>> Please upload!!
>>
>
> I've run into 2 pr
Hi,
Just another point of information, when you make your decision: I
work at a company where we frequently use Haskell and we use git for
almost all of our projects (other VCSs that we use are mercurial and
svn). Also, I use git for all of my open source projects and I find
that it works very we
Hi,
Just for fun, here is the code that does this:
newtype Int' = I Int deriving Eq
instance Show Int' where
show (I x) = show x
instance Num Int' where
I x + I y = I (x + y)
I 0 * _ = I 0
I x * I y = I (x * y)
I x - I y = I (x - y)
abs (I x) = I (abs x)
s
t;
> This is in a similar vein to Derek's approach, if
> accompanied by a little more grotesque whizzbangery.
>
> On 19 Jan 2009, at 21:51, Derek Elkins wrote:
>
>> On Mon, 2009-01-19 at 12:10 -0800, Iavor Diatchki wrote:
>>>
>>> Sure, the point is that you
Hi,
On Mon, Jan 19, 2009 at 11:06 AM, Jonathan Cast
wrote:
> On Mon, 2009-01-19 at 10:59 -0800, Iavor Diatchki wrote:
>> Hello,
>> The multitude of newtypes in the Monoid module are a good indication
>> that the Monoid class is not a good fit for the class system
>
>
Hello,
The multitude of newtypes in the Monoid module are a good indication
that the Monoid class is not a good fit for the class system (it is
ironic that discussing it resulted in such a huge thread recently :-).
How I'd approach the situation that you describe would depend on
the context (did
l give it a try in the coming week.
>
> Tom
>
> On Sat, Jan 3, 2009 at 8:18 PM, Iavor Diatchki
> wrote:
>> Hello,
>> Usually, you can program such things by using super-classes. Here is
>> how you could encode your example:
>>
>> {-# LANGUAGE MultiPara
Hello,
Usually, you can program such things by using super-classes. Here is
how you could encode your example:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances #-}
class HeaderOf addr hdr | addr -> hdr
class HeaderOf addr hdr => AddressOf hdr addr | addr -> hdr
data
Hi,
On Sun, Dec 21, 2008 at 11:45 AM, Luke Palmer wrote:
> 2008/12/21 Iavor Diatchki
>>
>>
>> g :: TestClass a => a -> Integer
>> g = fst (a :: (a -> Integer, a -> Integer))
>
> Which I believe needs to be written:
>
> g :: forall a. TestClass
Hello,
You can work around the monomorphism restriction with extensions but
to fix the ambiguity in your program that Reiner pointed out you'll
have to change the program to specify how you'd like to instantiate
"a".
here are all the types once again:
f :: (TestClass a) => a -> Integer
f = const 1
Hi,
There is some discussion about the different design choices relevant
for Haskell's class system in the following paper:
"Type classes: exploring the design space"
Simon Peyton Jones, Mark Jones, Erik Meijer
Presented at the 1997 Haskell Workshop.
Section 4.5 discusses options related to the res
Hello,
On Mon, Oct 13, 2008 at 3:16 PM, Stephen Hicks <[EMAIL PROTECTED]> wrote:
> 2008/10/13 Daryoush Mehrtash <[EMAIL PROTECTED]>:
>> Is there a write up on what makes an implementation lazy vs strict?
>
> I would be interested in seeing this, too!
Typically it has to do with the strictness of
Hello,
The currently released version of monadLib does not use overlapping
instances, indeed.
However, in the monadLib repo (http://github.com/yav/monadlib) there
is a file called "MonadLib4.hs" which contains a version of the
library that is implemented with overlapping instances, so you can
play
Hi all,
(this message is an ad:-)
For people interested in visualizing dependencies between the modules
in their project: on Hackage there is another simple tool called
"graphmod" that can generate a dot graph from your Haskell source
code.
-Iavor
2008/10/6 Magnus Therning <[EMAIL PROTECTED]>:
> O
Hi,
On Sun, Sep 14, 2008 at 7:01 AM, Stephan Friedrichs
<[EMAIL PROTECTED]> wrote:
> I agree that the MonadZero class with a useful 'zero' :: m a would be
> the right abstraction for views. But MonadZero is not part of base, mtl
> or any other common package, or am I missing something? Changing th
Hi Tim,
Your example seems like a perfect fit for functional dependencies.
On Thu, Sep 11, 2008 at 3:36 AM, Tim Docker <[EMAIL PROTECTED]> wrote:
> Well, it's a library that others might use, so I would prefer to avoid
> using language extensions, especially functional deps which I don't
> underst
Hi,
I just noticed that hackage has introduced a new policy to disallow
changes to a package without bumping the version. I understand that
this is probably a good idea for changes to the source code, but it
really would be nice to have a backdoor that allows for other changes.
For example, I jus
Hello,
The Haskell'98 report does not specify if/how recursive modules should
work. I wrote a paper a long time ago that formalizes and implements
this feature (http://www.purely-functional.net/yav/publications/modules98.pdf).
I very much doubt that separate compilation is much of a problem in
p
Hi,
On 7/29/08, Bryan Donlan <[EMAIL PROTECTED]> wrote:
> Hi,
>
> Is there any theoretical reason that functional dependencies can't be used
> to resolve a polymorphic type to a concrete type? For example:
>
>> -- compile with -fglasgow-exts
>>
>> class DeriveType a b | a -> b
>>
>> data A = A
>>
Hi,
"Purely Functional Data Structures" by Chris Okasaki is a good one.
Here is a link to it on Amazon:
http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504
Good luck!
-Iavor
2008/5/28 smellcode <[EMAIL PROTECTED]>:
> is there some book about haskell and data struct and
Hello,
I think that the modified API (no state monad, and using Maybe) is
quite nice! I implemented a version of the the suggested API using a
slightly different data structure, which makes the code a bit simpler,
I think. I put the code in the Haskell wiki:
http://www.haskell.org/sitewiki/image
Hello,
On Sat, May 3, 2008 at 3:56 AM, apfelmus <[EMAIL PROTECTED]> wrote:
> Bryan Donlan wrote:
>
> >
> > evaluate x = (return $! x) >>= return
> >
> > However, if >>= is strict on its first argument, then this definition is
> > no better than (return $! x).
> >
>
> According to the mo
Hello,
How about defining the types like this:
data PVal a = Unit a | Array [a]
data Val = IntVal (PVal Int) | BoolVal (PVal Bool) -- | etc
instance Serialize Int where ...
instance Serialize a => Serialize (PVal a) where ...
instance Serialize Val where ...
Hope this helps.
-Iavor
On Sun, Ap
Hello,
I am not sure of the use case here but you could also do the following:
data EvenList a = Nil
| ConsE a (OddList a)
data OddList a = ConsO a (EvenList a)
This does not use any type system extensions.
-Iavor
On Wed, Apr 23, 2008 at 4:46 PM, David Roundy <[EMAIL PROTECTED
Hello,
On Thu, Apr 17, 2008 at 12:05 PM, Martin Sulzmann
<[EMAIL PROTECTED]> wrote:
> Can you pl specify the improvement rules for your interpretation of FDs.
> That would help!
Each functional dependency on a class adds one extra axiom to the
system (aka CHR rule, improvement rule). For the ex
Hello,
On Thu, Apr 17, 2008 at 10:26 AM, Martin Sulzmann
<[EMAIL PROTECTED]> wrote:
> leads to an instance improvement/instance improvement conflict,
> like in the single-range FD case
>
> class D a b | a -> b
>
> instance D a a => D [a] [a]
> instance D [Int] Char
Sorry to be picky but ther
Hello,
On Wed, Apr 16, 2008 at 11:06 PM, Martin Sulzmann
<[EMAIL PROTECTED]> wrote:
> 3) Multi-range FDs
>
> Consider
>
> class C a b c | a -> b c
>
> instance C a b b => C [a] [b] [b]
>
> This time it's straightforward.
>
> C [x] y z yields the improvement y = [b] and z = [b]
> which then
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
Hi,
On Fri, Mar 28, 2008 at 6:42 AM, John Goerzen <[EMAIL PROTECTED]> wrote:
> On 2008-03-28, Don Stewart <[EMAIL PROTECTED]> wrote:
> > paulrbrown+haskell-cafe:
>
> > And we have a curl binding, already in wide use.
> >
> > http://code.haskell.org/curl.git/
> >
> > a release to hackage i
Hello everyone,
Just to clarify, the intended semantics of my example was that it
should behave as if we were to duplicate the common prefix:
server text
| Just xs <- parse text, "field1" `elem` xs = ... do one thing ...
| Just xs <- parse text, "field2" `elem` xs = ... do something else .
Hi,
We have no binary literals in Haskell and there are situations when it
would have been useful to have this feature (e.g., if the spec of
something that you are working with is already provided using this
notation).
While it may be useful to have overloaded binary literals in the usual
Haskell
Hello,
On 10/17/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> Check Wikipedia. Peirce law, law of excluded middle, double negation, ...
> they are all equivalent and it can be instructive to see how one can derive
> one from the other.
Apparently these axioms are not all equivalent (I was
Hello,
On 10/19/07, Martin Sulzmann <[EMAIL PROTECTED]> wrote:
> Simon Peyton-Jones writes:
> > ...
> > Like you, Iavor, I find it very hard to internalise just why (B) and (C)
> are important. But I believe the paper gives examples of why they are, and
> Martin is getting good at explaining
Hello,
I believe that this "weak coverage condition" (which is also called
"the dependency condition" somewhere on the wiki) is exactly what GHC
6.4 used to implement but than in 6.6 this changed. According to
Simon's comments on the trac ticket, this rule requires FDs to be
"full" to preserve th
1 - 100 of 147 matches
Mail list logo