kiwamu has been targeting an arm cortex-m3 succesfully with jhc. this
is a CPU with 40k of RAM running Haskell code very much on bare metal.
:)
John
On Tue, Mar 19, 2013 at 6:07 PM, Jeremy Shaw wrote:
> There have been at least a couple projects, such as hOp and HaLVM
> which attempt to run
I have merged your changes back into the main jhc tree. Thanks!
John
On Sat, Mar 16, 2013 at 5:28 AM, Kiwamu Okabe wrote:
> We are happy to announce Ajhc 0.8.0.2.
>
> It's first release announce for Ajhc.
> Major change on this release is ability to compile Haskell code for tiny CPU.
> There
p://www.youtube.com/watch?v=3R9sogReVHg
>
> And I created many patches for jhc.
> But...I think that the upstream author of jhc, John Meacham,
> can't pull the contribution speedy, because he is too busy.
> It's difficult that maintain many patches without any repositories,
> f
Is it any more ridiculous than
> f x@Nothing {} = fromJust x
> main = print (f Nothing)
crashing at run time? That is what you are expressing with your first
one. This issue is completely unrelated to the named field syntax,
they behave exactly like data types with non-named fields.
However, you
On Fri, Mar 30, 2012 at 1:05 PM, Mats Rauhala wrote:
> Oh wow, I thought jhc was discontinued, but just checked the
> repositories and mailing lists and it's alive and well. No idea where I
> got the idea that it was discontinued. Going a little bit on tangent
> here, but if I understood correctly
Why not
data Super
= SuperA {
commonFields :: ()
aFields :: ()
}
| SuperB {
commonFields :: ()
bFields :: ()
}
| SuperC {
commonFields :: ()
cFiel
On Fri, Mar 9, 2012 at 5:49 PM, Clark Gaebel
wrote:
> What's the advantage of using D.A.Storable over D.Vector? And yes,
> good call with creating an array of HSDouble directly. I didn't think
> of that!
Oh, looks like D.Vector has an unsafeFromForeignPtr too, I didn't see
that. so D.Vector shou
On Fri, Mar 9, 2012 at 12:48 PM, Clark Gaebel
wrote:
> static const double globalArray[] = { huge list of doubles };
> double* getGlobalArray() { return globalArray; }
> int getGlobalArraySize() { return
> sizeof(globalArray)/sizeof(globalArray[0]); }
>
> And importing it in haskell witht h
On Mon, Dec 19, 2011 at 7:10 PM, Alexander Solla wrote:
> * Documentation that discourages thinking about bottom as a 'value'. It's
> not a value, and that is what defines it.
The fact that bottom is a value in Haskell is the fundamental thing that
differentiates Haskell from other languages and
On Thu, Feb 16, 2012 at 1:20 PM, Ian Lynagh wrote:
> I've now implemented this in GHC. For now, the syntax is:
>
> type {-# CTYPE "some C type" #-} Foo = ...
> newtype {-# CTYPE "some C type" #-} Foo = ...
> data {-# CTYPE "some C type" #-} Foo = ...
>
> The magic for (Ptr a) is built in to
No, you can do nothing with the pointer on the C side other than pass
it back into haskell. It may not even be a pointer, it may be an index
into an array deep within the RTS for instance. The reason they can be
cast to void *'s is so you can store them in C data structures that
don't know about ha
On Thu, Feb 9, 2012 at 11:23 AM, Ian Lynagh wrote:
> On Thu, Feb 09, 2012 at 04:52:16AM -0800, John Meacham wrote:
>>
>> Since CSigSet has "sigset_t" associated with it, 'Ptr CSigSet' ends up
>> turning
>> into 'sigset_t *' in the gene
A good first step would be understanding how the other entry works:
cartProd :: [a] -> [b] -> [(a,b)]
cartProd xs ys = do
x <- xs
y <- ys
return (x,y)
It is about halfway between the two choices.
John
On Thu, Feb 9, 2012 at 9:37 AM, readams wrote:
> Nice explanation
On Wed, Feb 8, 2012 at 10:56 AM, Ian Lynagh wrote:
> That sounds right. It basically means you don't have to write the C
> stubs yourself, which is nice because (a) doing so is a pain, and (b)
> when the foreign import is inside 2 or 3 CPP conditionals it's even more
> of a pain to replicate them
Can't you do something like have the kind be unlifted? for instance
data Proxy (a :: #)
data Type1 :: #
data Type2 :: #
John
On Tue, Feb 7, 2012 at 12:19 PM, Douglas McClean
wrote:
> There are all sorts of useful functions that would otherwise require
> explicit type applications which w
On Tue, Feb 7, 2012 at 4:24 AM, Simon Marlow wrote:
> Separately the unix package added support for undecoded FilePaths
> (RawFilePath), but unfortunately at the same time we started using a new
> extension in GHC 7.4.1 (CApiFFI), which we decided not to document because
> it was still experimenta
That is one of the wonderful things about haskell, most languages have
a negative correlation between codesize and productivity, however with
haskell there is a strong positive correlation. You can re-use so much
that as your code base grows it becomes easier to add new features
rather than harder.
> As expected, no warnings. But if I change this "unfailable" code above
> to the following failable version:
>
> data MyType = Foo | Bar
>
> test myType = do
> Foo <- myType
> return ()
>
> I *still* get no warnings! We didn't make sure the compiler spits out
> warnings. Instea
wn, but independent sites
will find themselves shut off or delisted and sites linking to them
shut down.
John
On Wed, Jan 18, 2012 at 3:42 PM, Hans Aberg wrote:
> Actually, it is a battle between the Hollywood and Silicon Valley industries.
>
> Hans
>
>
> On 19 Jan 2012, at 00:1
And such a thing can take months or years for the courts to figure
out, and unless your free site has a lawyer to fight for your side,
under SOPA/PIPA you can be down the entire time with little recourse.
For anyone hosting content lke hackage, github, etc. when you have
thousands of packages, some
Not to mention ebay, craigslist, etc..
http://www.techdirt.com/articles/20111005/10082416208/monster-cable-claims-ebay-craigslist-costco-sears-are-rogue-sites.shtml
when there is no burden of proof for someone to take down a site then
things get very complicated.
for instance this package could b
Yes, they are major pains for frisby, which is a parser but needs to
be cleverer about recursion, the many and some that come with
applicative actually cause infinite loops.
John
On Sun, Dec 11, 2011 at 9:18 PM, Gregory Crosswhite
wrote:
> Hey everyone,
>
> I am sure that it is too late to d
People tend to concentrate on the lambda which cooresponds to the
functional aspect of haskell when designing logos. Not nearly enough
attention is paid to the other striking feature, the laziness. The
'bottom' symbol _|_ should feature prominently. The two most defining
features of haskell are tha
Um, the patch theory is what makes darcs "just work". There is no need
to understand it any more than you have to know VLSI design to
understand how your computer works. The end result is that darcs
repositories don't get corrupted and the order you integrate patches
doesn't affect things meaning c
On Fri, Apr 1, 2011 at 2:23 AM, wrote:
>
> John Meacham wrote:
>> Error is not catchable in haskell 98. Only things thrown by raiseIO are.
>
> I see; so GHC, absent any LANGUAGE pragma, should have arranged for
> `error' to generate a non-catchable exception.
Ac
Error is not catchable in haskell 98. Only things thrown by raiseIO are.
On Apr 1, 2011 12:02 AM, wrote:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
In general, errors are always interchangeable with another. An
exception in haskell is a value, rather than an event. Haskell
prescribes no evaluation order other than if the result is defined it
must be equivalant to the one generated by a normal-order reduction
strategy. Since error is not a vali
On Sun, Jan 30, 2011 at 4:44 AM, Roman Cheplyaka wrote:
> A few questions about the inclusion of parsec:
>
> 1. It is parsec-2, not parsec-3, right?
Yes, it is parsec-2. 2.1.0.1 to be exact.
> 2. Does this change consist of merely inclusion parsec as a standard
> library, or are there any comp
On Wed, Nov 10, 2010 at 11:33 AM, Lauri Alanko wrote:
> So a naive implementation of split would be:
>
> split g = (mkGen seed, g')
> where (seed, g') = random g
>
> (Where mkGen creates a new state from some sufficiently big seed
> data.)
>
> So what is the problem here? What kinds of observable
On Thu, Jan 13, 2011 at 3:07 AM, Stefan Kersten wrote:
> On 28.12.10 21:25, John Meacham wrote:
>> jhc generated C works on the android/ARM just fine. Android specific
>> libraries arn't available, so you would have to bind to what you want
>> with the FFI.
>
>
jhc generated C works on the android/ARM just fine. Android specific
libraries arn't available, so you would have to bind to what you want
with the FFI.
John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listi
On Sat, Dec 4, 2010 at 2:08 PM, Serguey Zefirov wrote:
> Why TypeRep does have equality and doesn't have ordering?
>
> It would be good to have that.
Yes, I have wanted that too. It would make maps from types to values
possible/efficient. There is a very critical path in jhc that use
type-indexed
On Tue, Dec 14, 2010 at 10:31 AM, Pierre-Etienne Meunier
wrote:
> Is there something like an identity type, transparent to the type-checker, in
> haskell ?
> For instance, I'm defining an interval arithmetic, with polynomials,
> matrices, and all that... defined with intervals. The types are :
A better plan would be to start depending on 'haskell2010' or
'haskell98' and get rid of explicit dependencies on 'base' altogether.
Since those are standardized between compilers.
John
On Tue, Dec 7, 2010 at 6:59 PM, Brandon S Allbery KF8NH
wrote:
> -BEGIN PGP SIGNED MESSAGE-
> Hash
On Thu, Nov 25, 2010 at 2:32 AM, Joachim Breitner
wrote:
> So I wonder:
> * Is sharing values of type Int (and Bool and similar small values)
> always safe?
> * If so: does GHC already do that?
> * Would it be technically possible?
> * Is there an established theory that can tell, for a sharin
-# LANGUAGE CPP #-}
> #define defObj(t) newtype t = t Obj deriving (A,B,C,D)
>
> defObj(Foo)
> defObj(Bar)
>
It has the advantage of being (de facto) portable.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
_
> Certificate a -> Certificate a
will work on valid or invalid certificates.
Just note that when changing a phantom type you need to reconstruct the
type fully. so for
> data A
> data B
> data Foo a = Foo Int
> conv :: Foo A -> Foo B
you can't write
> conv x =
difference gets more pronounced as
programs get larger. It is how I was able to write jhc for the most part
by myself. Haskell is an intelligence multiplier.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell
he two is fairly ideal.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
/repos/pappy/
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
. If anyone wanted to run
with this, I'd add it as a first class target platform for jhc.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Thu, Aug 05, 2010 at 04:08:38PM -0400, Nick Bowler wrote:
> On 2010-08-03 15:23 -0700, John Meacham wrote:
> > It is more an accident of ghc's design than anything, the same mechanism
> > that allowed threads to call back into the runtime also allowed them to
> &
On Thu, Aug 05, 2010 at 03:48:57PM -0400, wren ng thornton wrote:
> John Meacham wrote:
>> 'reentrant' and 'blocking' which could
>> be specified independently would be better and would be more
>> future-proof against changes in the RTS or between compile
This isn't to say ghc is doing the wrong thing, I don't think there
really is a right thing to do here given the broken class specifications
in the report.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
t that helps things right now really.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ad and
usage.
However, the instance definition for Either that mentions Error is
definitely a big misfeature in the library. Non-local returns are
generally useful in many contexts other than errors.
Actually, the 'Error' class in general seems somewha
ms of what they actually mean and presuppose a RTS
similar to ghcs current design. 'reentrant' and 'blocking' which could
be specified independently would be better and would be more
future-proof against changes in the RTS or between compilers.
John
--
John Meacham
combine values that appear in both maps
-> (b -> c) -- value appears in second map but not the first
-> (a -> c) -- value appears in first map but not second
-> Map k a -> Map k b -> Map k c
along with the 'WithKey' and 'Maybe' va
x27;t want to pre-create every possible
choice so encoding the size as a type level number makes sense.
I support complex numbers via a similar higher order type,
> data Complex_ :: # -> #
then I can use 'Complex_ Float64_' to get unboxed complex doubles.
John
--
J
fast algorithm under the hood.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
y2' :: exists m . Monad m => (m a -> a)
which you can read as "there exists some monad for which you can pull
out its value". The implementation is just the witness that proves that
Identity is one such monad, satisfying the existential quantification.
reakthough.
I thought there was some elegant way to express type level numbers
using balanced ternary, but I can't find a reference to it at the
moment.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ail
readers. Adding a completely different interface seems unnecessary and
fragmentary.
http://news.gmane.org/gmane.comp.lang.haskell.cafe
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ypes trick, the paper
talks about parameterized classes, though I wouldn't recommend them so
much, a useful trick sure, but not really essential for this task. the
two level type stuff is golden though.
unify:
http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.20.8205
I have
ation.cfm?id=773044
Ah, this paper looks very interesting, I was wondering if you had
experimented with prefetching just ahead of the allocation pointer.
Looks like it helped :)
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
7;t think they are really that different in capabilities.
Though, Jhc currently has a restriction that module names (real modules,
not re-exported ones) cannot ever conflict, even if hidden, so there is
a big difference in expressibility at the moment, but that is mainly due
to what I consider a bug in jhc
Apparently it was the indirection short
circuiting that GC performed that did it. Saving that cache line fill
for the redirection node was a huge win that made up for the GC cost.
(cachegrind of the valgrind suite is a great tool for figuring this sort
of thing out). T
address of a stack allocated object will inhibit certain gcc
optimizations.
The underlying allocator is based on Bonwick's slab allocator[2] which
works quite well for a haskell runtime, I have a slab for each type, so
a slab of 'cons' cells, a slab of size 3 tupl
can you send me some information on your system? like the
output of 'uname -a' and 'gcc --version'?
Thanks for the patch, I'll apply it.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Ca
On Sun, Jul 11, 2010 at 12:13:48AM -0400, Brandon S Allbery KF8NH wrote:
> On 7/11/10 00:10 , John Meacham wrote:
> > I switch the -wholename to -path which my 10.5.8 OSX seems to think is
> > okay and it works on linux. It isn't in the POSIX standard but appears
> > w
sts. Hmm...
Windows cross compiling seems a little broken too, but the fix looks
easy. I can add windows compilation to the regression test thankfully
due to wine so I can fix it for the next release.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
he Makefile.in is generated by
automake and will be regenerated by autoreconf, where in the Makefile.am
(which I wrote) are you refering to?
> Also, all of the "find" invocations assume the default action is "-print";
> this will silently fail on Solaris and ot
On Sat, Jul 10, 2010 at 05:38:02PM -0400, wren ng thornton wrote:
> John Meacham wrote:
>> On Sat, Jul 10, 2010 at 04:01:53PM -0500, Antoine Latter wrote:
>>> * running DrIFT on src/E/TypeCheck.hs fails with an illegal
>>> bytesequence in hGetContents. I'm gue
jhc if you're interested. I can't test it properly, though, with
> the compiler crash above.
Try without the '-v' flag, it shouldn't try printing the non ascii
character then. or modify src/Stats.hs and replacet all the C.
constants with ascii equivalants. If there is a g
ed (and the report mentions all the operations with undefined
results), if anything it should be left for
instances to decide based on the underlying algebra of the specific
type and the report shouldn't mention it.
John
--
John Meacham - ⑆r
pports garbage collection and a speedier runtime and
better support for external build systems will be out soon. My goal is
one more point release before 0.8.0 which will have full haskell 2010
and 98 support.
John
--
John Meacham - ⑆repetae.ne
Are you sure you are interpreting what 'die' should do properly? Your
code makes sense if die should decrement your life counter and continue
along, however if 'die' is meant to end your whole game, then there is
another implementation that does type check.
Jo
).
The context isn't a string. it is an intermediate state in the algorithm
of the hash function. it is usually an opaque binary blob (represented by a
ByteString) of a size that is on the order of the final hash (unrelated
to the size of the input).
John
--
e State monad or something like that?
Not using the state monad allows explicit sharing/storing of the
context, which would be quite handy if you arn't hashing your whole
input in one go.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
__
ow a lot of that goes
on inside the compiler.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
and start using fgl-6
internally without modifying its external API. Suddenly you are
incompatible without a version number bump anywhere due to a completely
non-local change.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
__
On Tue, Jun 22, 2010 at 06:24:22PM +0100, Andrew Coppin wrote:
> John Meacham wrote:
>> In particular, a Huffman coding:
>> http://en.wikipedia.org/wiki/Huffman_coding
>> is ideal for this (assuming you just are taking advantage of frequency
>> analysis). A dynamic Huff
articular, a Huffman coding:
http://en.wikipedia.org/wiki/Huffman_coding
is ideal for this (assuming you just are taking advantage of frequency
analysis). A dynamic Huffman Tree will even adapt as it is being used to
whatever the current language is. Huffman Trees are easy and fun to
implement too.
p unrolling
optimization, which is a fairly common thing for a compiler to do.
However, as you described it, it is not actually a valid optimization in
haskell. compare
take 2 (matchPattern5 (1:2:3:4:undefined)) => undefined
take 2 (matchPattern (1:2:3:4:undefined)) => [1,3]
John
-
stribute it. They are already under no obligation to distribute your
work or make it available.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Wed, May 26, 2010 at 01:17:00PM -0700, Evan Laforge wrote:
> Unfortunately then you get another cockamamie restriction in the whole
> JVM vs. tail calls thing... but if you can get around that then lots
> of people will like you a lot.
Working on it... :)
John
--
Joh
class aliases' proposal was meant to solve this issue with type
classes.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
r g) => FunctorPair f g where
transformFunctor :: f a -> g a
though, I am not sure what your use is, there isn't an obvious instance
to me, but I don't know what your motivating task is.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
_
her constructor to Foo will suddenly change the type of do
notations involving it non locally. said constructor may not even be
exported from the module defining Foo, its existence being an
implementation detail.
All in all, it is very hacky one way or another. Much more so than
having &
a
> 'set' for each variable?
Yup.
foo.c:
int my_int;
Foo.hs:
foreign import "&my_int" my_int_ptr :: Ptr Int
foo = do
poke my_int_ptr 4
x <- peek my_int_Ptr
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
sult is unused, like 'mapM'. This would be similar to what
gcc does, where you can specify an attribute saying a functions result
should be used or the compiler should complain.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
they
don't occur at run time, you can't pretend they don't exist when
reasoning about the meaning of a program, any more than you can
reasonably reason about haskell without taking types into account simply
because types don't occur in the run-time re
theoretically subdivide the binding group, typing f
alone, getting its most general type, then typing y, then going back and
verifying y's use in f is valid. It is ceratinly possible to come up
with a specification for an extended type inference algorithm such as
this, but whether it is worth it is
On Sat, Mar 27, 2010 at 07:30:30PM -0300, Rafael Cunha de Almeida wrote:
> John Meacham wrote:
> > Here are jhc's timings for the same programs on my machine. gcc and ghc
> > both used -O3 and jhc had its full standard optimizations turned on.
> >
> > jhc:
> >
My friend named her cat Haskell after the language :)
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
This is certainly something I could use.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ystem 96% cpu 32.200 total
As you can see, jhc shines at this example, actually beating gcc -O3. It
isn't too surprising, this is exactly the sort of haskell code that jhc
excels at.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://nota
ork on any type of point.
You may want to create a class that converts between the two
> class Coordinated f where
>toCartesian :: f Spherical -> f Cartesian
>toSpherical :: f Cartesian -> f Spherical
>
> instance Coordinated Point where ..
ntial bottom implys an 'eval' somewhere). Depending on your code,
all things may not be equal and there are rare times when the tupled
version is more efficient however.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
_
rst cross-platform targets I tested with.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ferent space usages.
xs = 'x':xs
id xs => constant space
map id xs => potentially infinite space
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
, 10^-44 seconds or so. Or is that only relevant to our ability to
_measure_ things at that scale and not the continuity of time itself as
far as QM is concerned?
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell
=> Set a = ...
like Jan-Willem suggests, then it seems that 'Set' should not be able to
unify with 'item' since it has the extra 'Ord' consraint on the
contravariant argument to item and item is universally quantified. Item
would need a psuedo-type l
'e',Down 'f']
Set.toAscList sxs2
[Down 'f',Down 'e',Down 'd',Down 'c',Down 'b',Down 'a']
We have been able to break the invarients of 'Set' using newtype
deriving of a completely unrelated class 'Iso&
or random uploaded packages,
it can't know if the GPL licenses have special exceptions or whatnot.
Unless of course someone where to write a formal combinator
language for expressing legal contracts.. :).
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
_
ions to INLINE
- qualified method names fix
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
local
instances) is a main _feature_ of type classes. Often when people think
they need local instances, they are just applying type classes when they
should be using a different idiom, such as the one you mention.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
formed the base of the original type checker for jhc. It
has since been fully replaced, probably twice over, but jhc could not
have gotten off the ground without it.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
is recommended you directly include the
modules into your program and modify them with the specific parameters
appropriate to your task.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Ha
side effect
is that jhc is very lightly coupled to any particular RTS, so
experimenting with alternate ones is pretty straigtforward.
John
--
John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/
___
Haskell-Cafe mailing list
Haskell-Cafe@haske
1 - 100 of 513 matches
Mail list logo