On 6 April 2010 05:32, Ivan Miljenovic wrote:
> 5) No-one is convincing anyone else to their point of view, so we have
> a stale mate.
Let me summarise the main arguments against the restriction:
1. It stops people from contributing to hackage. (It is immaterial
that if you were in their positio
On 6 April 2010 05:01, Luke Palmer wrote:
> When you say convincing, you are talking about yourself being
> convinced, right? So this paragraph means "The arguments against my
> position haven't convinced me, but the arguments for my position
> have."
Had I been told a convincing reason for the
2010/4/6 Jonas Almström Duregård :
> Maybe users could choose between using a real name and being given a
> random one (like Anonymous). This will (1) protect from data
> mining, (2) protect from government persecution and (3) keep the
> damned 1337 Haxxor names away from Hackage :)
I think this i
On 5 April 2010 23:52, Jason Dusek wrote:
> There certainly is a significant subculture of anonymity on
> the internet but maybe it has spread beyond its useful limits?
> There are places where it is helpful (Allberry's examples
> above come to mind) but I don't think contributing code to
> H
On 5 April 2010 12:52, Ross Paterson wrote:
> Basically http://meatballwiki.org/wiki/RealNameUserAdvantages, especially
> simplicity, trust and recognizability.
Allow me to respond to some of these points. I find none of them
particularly convincing, especially not when compared to the
disadvanta
.On 5 April 2010 03:57, Ivan Lazar Miljenovic wrote:
> I can understand wishing to be anonymous in these kinds of situations,
> but in terms of submitting open source software? Unless their employer
> is worried about them releasing proprietary software on Hackage, I don't
> see the potential for
Hi,
An issue came up on #haskell recently with Hackage accounts requiring
real names. The person in question (who didn't send this email as he's
wishing to remain anonymous) applied for a Hackage account and was
turned down, as he refused to offer his real name for the username.
Those of us in th
2008/8/31 Ryan Ingram <[EMAIL PROTECTED]>:
> My proposal is to allow "ad-hoc" overloading of names; if a name is
> ambiguous in a scope, attempt to type-check the expression against
> each name. It is only an error if type-checking against all names
> fails. If type-checking succeeds for more tha
2008/8/29 Philip Weaver <[EMAIL PROTECTED]>:
> It sounds like you tried to redefine (>>) and (>>=) and make 'do' use the
> new definitions. This is not possible, regardless of what types you give
> (>>) and (>>=).
Watch out for rebindable syntax:
http://www.haskell.org/ghc/docs/latest/html/users_
2008/8/29 Maurício <[EMAIL PROTECTED]>:
> x :: Prelude.Monad a
> y :: Prelude.Monad b
> foo :: b -> Prelude.Monad c
Monad is not a type, it is a type class, so you probably mean:
x :: Monad m => m a
y :: Monad m => m b
foo :: Monad m => b -> m c
With the further understanding that all three `m'
2008/8/28 Maurício <[EMAIL PROTECTED]>:
> After the explanations, I think I got it, and just
> updated the wiki.
Glad you've understood it. Seems I arrived a little late at this
thread, but there is also:
http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching
In addition, the first
2008/8/25 Ketil Malde <[EMAIL PROTECTED]>:
> 1. Etch comes with ghc-6.6, and that didn't work with my .cabal file.
Is it not an option to make your software work with the
not-quite-latest compiler? 6.8 is less than a year old, so I imagine
6.6 is still in quite a few major distro's stable reposito
2008/8/17 Eric Y. Kow <[EMAIL PROTECTED]>:
> Correction! We have a tentative offer for space near *Cambridge*
> (thanks to Ganesh) and to Ian for picking up on the blunder.
Where exactly?
--
-David House, [EMAIL PROTECTED]
___
Haskell-
27;em!)
A useful rule to remember with guards is that "once you cross the equals sign,
you can't go back". So if one of your patterns matches and a guard on that
pattern is true, that right-hand side will be evaluated and there is no way to
fall back to another guard or pattern.
--
-Da
Peter Padawitz writes:
> Is f(~p(x))=e(x) semantically equivalent to: f(z)=e(x) where p(x)=z?
Yep.
See also http://en.wikibooks.org/wiki/Haskell/Laziness#Lazy_pattern_matching
regarding lazy patterns.
--
-David House, [EMAIL PROTECTED]
___
Hask
gets
resolved, which probably won't be until associated types get fully implemented
in GHC, a new version of GHC gets released and people start to use them.
[1]:
http://hackage.haskell.org/trac/haskell-prime/wiki/MultiParamTypeClassesDilemma
;t work with GHCi if it works with GHC. They use the same code to compile
it.
On the other hand, you could always just set up a Makefile (which is pretty
trivial) and use M-x compile (which you should bind to a key if you use it a
lot).
--
-David House, [EMAIL PROTECTED]
__
27;ll put a list here..."
The design stage of any Haskell program should include a lot of time thinking
about your data structures, type classes, and how they all interact. If anything
this plays a larger role than in OOP.
--
-David House, [EMAIL PROTECTED]
___
http://en.wikipedia.org/wiki/Graph_theory
> > Data.Tree -- rose tree type
> >
>
> What's a rose tree? (I only know about binary trees. Well, and N-ary
> trees... but nobody uses those.)
Well, it is said that a rose tree by any other name would be just as N-ary. (
-ended sequence type supporting a fast variety of operations
quicker than lists
Data.Graph -- graph type
Data.Set -- unordered collection
Data.Tree -- rose tree type
And those are just the ones distributed with GHC.
--
-David House, [EMAIL PROTECTED]
___
H
t
polished. By all means, try it out, and if it doesn't work, feel free to submit
patches, but I doubt it'll get changed any time soon by a haskell-mode developer
:)
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
n that it would
be arcane and impossible to learn. But it's the most powerful editor around
today, and let me tell you, if you can learn Haskell, you can certainly learn
Emacs :)
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
to get used to, but its power makes it worth it. Give it a
fair try over a weekend or so, count the experience as gaining a life skill.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/ma
u cited I gave links and
screenshots to the Emacs equivalents, none of which (AFAIK -- I don't actually
use them all) use ASCII art.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Marc Weber writes:
> Eclipse does have this which saves you a lot of time:
> Fix imports.
Could you describe the semantics of that more precisely?
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.or
27;t been anti-aliased. By checking out the unicode-2 branch of Emacs, which
will be merged into the trunk before Emacs 23, you can easily get XFT support. I
wouldn't live without it.)
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
en jump to the Emacs tour [2] to whet your appetite to the
breadths of features that Emacs provides.
[1]: Use C-h t (hold Ctrl, press h, then let go of both and press t) inside
Emacs
[2]: http://www.gnu.org/software/emacs/tour/
--
-David House, [EMAIL PROTECTED]
___
for us all to look at.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
any
lifetimes to replicate this in a different language.
I've thought a little about writing a Haskell → Elisp compiler, so that people
could contribute to Emacs by writing Haskell, but I've got doubts about its
feasibility.
--
-David House, [EMAIL PROTECTED]
2005, IntelliJ IDEA or Eclipse.
Would you rather have a different editor for every language, and be forced to
learn new editor paradigms, keyboard shortcuts, tools and so on, or have one
editor for every language? This is one of Emacs's greatest strengths, IMO: it
can handle _everything_.
--
-Da
mes you call it. It's possible to break this
property using this trick.
2) Not use polymorphic references, as they lead to type unsafety [1].
3) Always use the {-# NOINLINE #-} pragma on any IORefs you create this way.
[1]:
http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO-Unsa
g, so no breakpoints, but just
> plugging in a visualizer/pretty printer for a function in a separate
> dedicated window, like what http://www.apple.com/shake does on each "node")
Debugging in Haskell is a bit of a no-show for now. There's some support in the
latest versions of GHCi
not really a "feature".
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
7;d be successful and return Right.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
neither is
a subset of the other, so {1, 2} ≤ {4, 5} is false, but {4, 5} ≤ {1,
2} is false, too.
http://en.wikipedia.org/wiki/Partial_order contains a formal
definition and a few more examples.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
(x:xs) -> [(x, xs)]
parse :: Parser a -> String -> [(a, String)]
parse (P p) inp = p inp
You should find with those definitions that you can write p as you would expect.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
azy
pattern). So it becomes the right hand side, C . Only when you
force that would you have to force the undefined argument, so
foo undefined = C undefined:
*Main> foo undefined
C *** Exception: Prelude.undefined
--
-David House, [EMAIL PROTECTED]
__
Ah, sorry, then disregard my solution. I did wonder why you'd
immediately jump to Data.Bits.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
loat number, and
returns a list of digits and an exponent."
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
modules loaded: none.
It seems to be wanting a more general instance than the one I'm
providing, for whatever reason. Using print ((2 :: Endo Integer) 3)
works, but that's hardly satisfactory.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
t are ready to
do the unrolling again.
(Adapted from pp59-60, Types and Programming Languages, Benjamin C. Pierce.)
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 29/05/07, Antti-Juhani Kaijanaho <[EMAIL PROTECTED]> wrote:
Well, not quite :) You forgot "-> Bool" at the end :)
Ha! Sorry, what a lovely ironic typo. :)
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haske
On 29/05/07, Daniel McAllansmith <[EMAIL PROTECTED]> wrote:
Just in case there was some sort of miscommunication, the actual answer to
your question is (/=) :: a -> a -> Bool, as Neil said.
Almost, (/=) :: Eq a => a -> a.
(Just for completeness.)
--
-David House
On 28/05/07, Rodrigo Queiro <[EMAIL PROTECTED]> wrote:
After a little too long trying, I managed to get code from which the type
system will infer that type, without using 'undefined':
Yes, but you do it by writing a coerce :: a -> b, which is surely cheating.
--
-
u want to
write some generic code to handle the addition of any one of these --
so this one piece of code allows you to add a new forum, thread or
post. Without a splattering of type-system extensions (I used at least
MPTCs, FDs and existentials), this isn't going to be possible.
--
-David Ho
orphism), along with
multi-parameter type classes, some kind of resolution to the "MPTC
dliemma" -- so functional dependencies or associated types or
something similar -- and perhaps GADTs are really the only large type
system extensions likely to make it into Haskell-prime. They're
that "there are 8 days in the week" is true. Hence, the statement
can't be false, so it must be true.
(I'm ignoring the difference between truth and provability; think of
my arguments as classical rather than intuitionistic.)
--
-David House, [EMAIL PROTECTED]
_
uldn't describe that as "just used by Haskellers".
It's also interesting to note that there's a fairly large percentage
of Ruby users using darcs. Perhaps we out to push more on this front?
--
-David House, [EMAIL PROTECTED]
___
Ha
e themselves as
Haskellers. See http://www.emacswiki.org/cgi-bin/wiki/DaRcs for a few
links.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
t that wouldn't still be usable at run time...) I imagine newIORef
as mallocing() some room, then returning a pointer to that memory.
That doesn't seem like something that could be done at compile time.
--
-David House, [EMAIL PROTECTED]
___
Ha
On 23/05/07, David House <[EMAIL PROTECTED]> wrote:
Why should it compile? Expressions in a do-block have to have the type
m a for some monad m, don't they?
Further developments on #haskell:
dmhouse: where in the report does it say that do blocks constrain
types inherently?
ve the type
m a for some monad m, don't they?
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
where it's defined, it's type and so on, but not Haddock
documentation. I'm extending haskell-mode's inf-haskell.el to take
this into account.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
On 19/05/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
How about this?
do
y <- if x < 0
then do ...
else do ...
As with many other things in Haskell, the rule is "Give it a go and
see if it works!" You should find that the above code runs fine.
-
ver the do-block they're contained in. Here y
is out of scope once you leave the inner do-block. The solution is to
do something like the following:
do
let y = if x < 0 then 5 else 8
print y
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing li
gs in order for it to work. The corresponding GHC flag is
-fglasgow-exts. Try that.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
z x
foldr f z (x:xs) = f x (foldr f z xs)
f-+--+
| |
x foldr-+--+--+
| | |
f z xs
Tail recursion, then, expresses the idea that a function appears at
the top of its call stack, or at the top of the tree of its right-hand
side. It's got nothing to do with evaluation ord
<- [0..x + 1]
return y
Or to bypass layout altogether:
let { b = sum $ do
y <- [0..x + 1]
return y }
(Of course, in this specific case I'd write sum [0..x + 1], but I
guess that this is an example of a general case.)
--
-David House, [EMAIL PROTECTED]
_
On 16/05/07, Sergey Perminov <[EMAIL PROTECTED]> wrote:
How to solve task of reversing big list with constant heap space used?
I think that as lists are singly-linked in Haskell, reversing a list
will always be O(n) space.
--
-David House, [EMAIL PRO
nd, and its being written in Emacs Lisp doesn't help the
matter! Still, it's on my todo list.
[1]: http://haskell.org/haskell-mode
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 10/05/07, Dan Weston <[EMAIL PROTECTED]> wrote:
I've been pronouncing monad like gonad (moh-nad), but it occurs to me
that it might be pronounced like monoid (mah-nad).
You say monoid mah-nad? I've always said mon-oyd, to rhyme with void or annoyed.
--
-David House,
)
f = return negate >>= g (4 :: Int) (1 :+ 2)
You're attempting to pass the rank-2 polymorphic function "g (4 ::
Int) (1 :+ 2)" as a parameter to (>>=), which doesn't work.
General point: couldn't GHC's error reporting be improved at times like these?
--
-> n) -> return (fn r, fn s))'
I.e. why does the polymorphism get destroyed?
Here fn is bound by a lambda abstraction, and is therefore
monomorphic. I can't find anything in the Report about that, but that
is how it works. It might be how a H-M type system works in general,
I'm not
of high level because the lack of a _|_
will bite you sooner or later.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 06/05/07, Duncan Coutts <[EMAIL PROTECTED]> wrote:
Try the latest darcs version of c2hs, it has a new C parser which should
fix issues like this. We should have a new tarball release soon.
Works great. Thanks very much.
--
-David House, [EMAIL PRO
ble-click it just so that I can try stuff out in GHCi...
Any reason you can't use :module Blah in GHCi?
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
; option? That's what it's called in Gmail,
you just have to remember to click that instead of the vanilla
'Reply'.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
're reading this as a competent Haskell programmer, why not
spend an hour or so improving one of the advanced sections? If there's
something you want to write about but that isn't a current chapter,
just start it anyway and we'll include it in.
[1]: http://en.wikibooks.org/wiki/Haskel
7; does not fit here.
Setup.lhs: got error code while preprocessing: Network.GnuTLS.GnuTLS
c2hs version:
I've attached the file it references in case that's relevant. Any tips
on how I might address this?
Thanks in advance,
-David House, [EMAIL PROTECTED]
/* Copyright (C) 2002, 2003, 20
On 05/05/07, Andrew Coppin <[EMAIL PROTECTED]> wrote:
I just had a thought... Why doesn't somebody implement a spreadsheet where
Haskell is the formula language? 8-)
http://sigfpe.blogspot.com/2006/11/from-l-theorem-to-spreadsheet.html
may interest.
--
-David House, [EMAI
On 2 May 2007 16:16:57 -, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:
* It would be nice if this worked inside the do-notation, too:
do x :: Ordering
x <- m
(This is curently a syntax error.)
I think the following works with -fglasgow-exts:
do (x :: Ordering) <-
tance looks like this:
instance Functor MyMaybe where
fmap f (MM a) = MM (fmap f a)
The instance just unwraps and rewraps the newtype constructor.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.
On 29/04/07, David House <[EMAIL PROTECTED]> wrote:
It's worth pointing out that Emacs's haskell-mode already has this.
For anyone that uses the major mode but hasn't heard of the
inf-haskell features:
I did forget to mention that this won't help with your &
c M-. inferor-haskell-find-definition: jumps to the definition of
the function, class or datatype etc. under point.
See the Haskell wiki page [1] for more information.
[1]:
http://haskell.org/haskellwiki/Haskell_mode_for_Emacs#inf-haskell.el:_the_best_thing_since_the_breadknife
--
-Dav
o it should be fixed, no matter how well the
workaround is documented.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
gle.el [5] and hpaste.el
[6].
Enjoy!
[1]: http://www.haskell.org/haskell-mode/
[2]: http://haskell.org/haskellwiki/Haskell_mode_for_Emacs
[3]: http://haskell.org/hoogle
[4]: http://hpaste.org
[5]: http://haskell.org/haskellwiki/Hoogle.el
[6]: http://haskell.org/haskellwiki/Hpaste.el
--
-David
On 09/04/07, Albert Lee <[EMAIL PROTECTED]> wrote:
mapM putStrLn files
Seeing as you're not doing anything with the results of this map, you
probably want to use mapM_ instead. Then the result type of ls_dir1
can be IO (), which is neater.
--
-David House, [EMAI
[a -> a] ->(a -> a) could be
defined. Most are quite silly, but the solution involving the State
monad, for example, is really quite elegant.
[1]: http://haskell.org/haskellwiki/Compose
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing l
inom n r = fac n `div` (fac r * fac (n - r))
Remember that prefix function application has a higher precedence than
pretty much anything else.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
qux, quux, foo,
bar, baz, qux ]
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ned before, some combinators are so ubiqutos they're almost like
syntax. Seeing as the actual syntax will always be in scope, these
common combinators would also have to be in scope all the time, which
means placing them in the narrowed Prelude.
--
-David Ho
would the import pull in
the 'wider' Prelude, with a more expansive selection, more akin to the
current Prelude?
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ontrol structures in other languages.
As real control structures, like if and case, are always in scope,
having _no_ functions imported by default would drive an unnatural
wedge between function and control structure.
--
-David House, [EMAIL PROTECTED]
___
flip
($)
2. To make including literals sane
Char
String
Int
Integer
Num(..)
3. Other basic functions
Eq(..)
Ord((<), (>), (<=), (>=))
Show(show)
4. Miscellaneous
id
const
undefined
Of course, the precise details would be debateable.
by a 'module M where' declaration, as suggested by
Sebastian.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
email to ask for this mailing list on the haskell.org site.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ing this without
your average numeric function needing about a thousand different
constraints on it. Type class synonyms [1] look promising, but
no-one's implemented them yet AFAIK.
[1]: http://repetae.net/john/recent/out/classalias.html
--
-David Ho
dicate (==) applies to. I
don't see this as ugly; quite the contrary, in that if you know a type
instantiates Eq you can use (==) without worrying about using a
type-specific equality predicate. E.g. it's nice to see the same (==)
everywhere rather than seeing (say) (Int.==), (Bool.==) and so on.
splitting up type classes. Type class synonyms -- google for
them -- look like a good solution, but are lacking an implementation).
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 10/03/07, Joachim Breitner <[EMAIL PROTECTED]> wrote:
Is there a name for these functions? "Characteristic Church Encoding
Functions" maybe? Are there more than these:
Catamorphisms is indeed the name I've heard.
--
-David Ho
. There is no
such clash with type constructors as there are no type functions.
Hence the classic example:
class Arrow (~>) where ...
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
bably needs -fglasgow-exts.) Sadly we don't have a fixity system
for type operators :(
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
n on ($) and similar hofs. I tend to use ($) only when the
right-hand side gets very messy; a multiple-line do or similar. For
example:
blah = fromMaybe $ do
x <- blah1
y <- blah2
guard (x == f y)
g x
The closing parenthesis would make things a little messy, so ($) i
nts on every
project.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
unctions, but x is not a
function, it is a value, so you have to apply it to the composite
function f . g . h using the ($) operator or parentheses.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.hask
orphic type variable, could not be unified with `Char', a
monotype.)
In the expression: "hello" at ~/foo.hs:1:8
In the definition of `foo': foo = "hello"
How's that sound?
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
7;a' with Int, which is wrong. What would a nicer error message
say?
"Inferred type was monomorphic but a polymorphic type was given", or
something. Hugs says "Inferred type not as polymorphic as expected",
which is the
e my email asking
whether there's a good reason it's not possible. I guess there are no
theoretical limitations, because, as you've just shown, you can hack
your way around it.
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe ma
o be a method of the class:
{-# OPTIONS_GHC -fglasgow-exts #-}
class Foo a b | a -> b where
foo :: Foo b c => a -> Maybe c
instance Foo String () where foo _ = Nothing
instance Foo Int String where foo 4 = Just (); foo _ = Nothing
--
-Davi
ugs's "Infered type is not general
enough").
--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
1 - 100 of 202 matches
Mail list logo