g "Base candidates". The
bike shedding on the Libraries list, whilst frustrating for a
proposer, is valuable for teasing out more regular designs than single
authored packages often manage, and having lots of small packages for
Base-like things is a dependency
On 23 December 2010 21:43, Mario Blažević wrote:
> Why are Cofunctor and Comonad classes not a part of the base library?
[SNIP]
> Later on I found that this question has been raised before by Conal Elliott,
> nearly four years ago.
>
> http://www.haskell.org/pipermail/libraries/2007-January/006740
On 23 December 2010 22:01, Henning Thielemann
wrote:
>
> This could be seen as "type Step st a = (Maybe a, st)". I have thought about
> mapping from [Int] to [Maybe (Int, Int)] by mapAccumL, then compressing the
> result with catMaybes. However we need to append a final pair when the end
> of the
On 23 December 2010 21:12, Stephen Tetley wrote:
> I'd go with direct recursion for this one - the pattern of consumption
> and production that generates the answer doesn't seem to neatly match
> any of the standard recursion combinators (map, unfold, fold,
> mapAccum
I'd go with direct recursion for this one - the pattern of consumption
and production that generates the answer doesn't seem to neatly match
any of the standard recursion combinators (map, unfold, fold,
mapAccum, ...) nor exotic ones (skipping streams c.f. the Stream
fusion paper, apomorphisms, ...
Maybe you want to hide the old version of regex-posix:
> ghc-pkg hide regex-posix-0.94.2
http://www.haskell.org/ghc/docs/7.0.1/html/users_guide/packages.html
Note - I don't use cabal install myself so this might not be the right
way to do things, however "ghc-pkg hide ..." is reversible with
"gh
You might want to look at Malcolm Wallace's HMake - there is both the
code and a paper describing it. Quoting the paper:
"hi - hmake interactive - is a small program, itself written in
Haskell, which imitates many of the interactive features of Hugs."
_
On 20 December 2010 21:24, Stephen Tetley wrote:
>
> Although I haven't tried myself, I think it can be fixed by upgrading
> with cabal - [SNIP]
>
To be explicit - that's upgrading just regex-posix with Cabal not the
whole Platform.
__
I think broken posix-regex is a known issue with the last release of
the Platform on Windows.
Although I haven't tried myself, I think it can be fixed by upgrading
with cabal - although regex-posix is a FFI binding, in this case all
the parts (headers and C library) are bundled with the platform s
On 12 December 2010 13:03, Max Bolingbroke wrote:
>
> type instance DUnit (a,b) = GuardEq (DUnit a) (DUnit b)
>
> type family GuardEq a b :: *
> type instance GuardEq a a = a
Thanks Max, that seems to be what I need.
Best
pe instance (DUnit a ~ DUnit b) => DUnit (a,b) = DUnit a
I don't want to pick an arbitrary side, e.g:
> type instance DUnit (a,b) = DUnit a
or
> type instance DUnit (a,b) = DUnit b
Thanks
Best wishes
Stephen
_
Andy Gill developed HERA which sounds somewhat similar to what you are
asking, but I don't know that it would be particularly beginner
friendly and I think it was static - i.e. the reduction rules were
applied to program source code rather than within an interactive
evaluation of a running program.
On 20 November 2010 12:05, Tillmann Rendel
wrote:
> I would expect the "exponential type" to be (a -> b):
>
Terminologically, "Bananas in Space" (!) agrees with you.
http://www.cs.nott.ac.uk/~gmh/bananas.pdf
Regards
Stephen
___
On 19 November 2010 22:17, Brandon S Allbery KF8NH wrote:
> If a Perl "expert" tells you that regexps are the way to parse HTML/XML, you
> can safely conclude they've never actually tried to do it.
For the original message it sounded like the Perl expert recommended
regexps to scrape facts from
On 18 November 2010 00:37, Henk-Jan van Tuyl wrote:
> If you use MinGW, your compiled program depends on mingwm10.dll (depending
> on the version of MinGW).
Is this true in general or only when you have bindings pulling it in?
The MinGW site and other places found in a search indicate that this
Cygwin is fine for development - the shell is Bash (this can probably
be changed), so it is much more capable than the MS shell. Personally
I've never needed to uninstall Cygwin, if things get in a mess
re-running the Cygwin installer seems to sort things out.
One caveat is that if you want to bui
On 12 November 2010 21:48, Jonathan Geddes wrote:
>
> I cringe to imagine what the equivalent is in current Haskell syntax.
> Anyone want to try it? Not me!
Perhaps not pretty - but it is regular and avoids Template Haskell an
manages for the few times I have records-in-records:
doubleInner3OfA
On 12 November 2010 20:44, Andrew Coppin wrote:
> Just today I was thinking about how useful it would be if you could send a
> block of code from one PC to another to execute it remotely. The fact that
> you can't do this is basically why there's no distributed Haskell yet,
> despite what an obvi
On 12 November 2010 20:33, Malcolm Wallace wrote:
> Either that, or people find it awkward to deal with the substantial
> extra hierarchies of type classes.
After the initial version in in PDFS it also developed operation
bloat. e.g. the added Sequence class has many methods that don't fit
well
On 11 November 2010 21:23, C. McCann wrote:
> [Snip] What started
> this thread, however, was the idea of a serialization function
> producing something like a pure ByteString, and why that, as opposed
> to (IO ByteString), would be extremely problematic.
I think the original poster was intrigu
Apologies - an unfortunate typo in my first sentence (extra "don't") ,
it should have read: :
> But I don't see that you need introspection at user level for
> persistence, a dynamic type will do, thus the internals aren't open to
> inspection. Whatever introspection is necessary can be handled by
But I don't see that you don't need introspection at user level for
persistence, a dynamic type will do, thus the internals aren't open to
inspection. Whatever introspection is necessary can be handled by the
runtime system as in Clean and Persistent Haskell. You could look at
the internals of a pi
Have you tried with double backslash \\ and starting from the root? I
think runhaskell under MinGW uses this form:
> runhaskell Setup.hs configure
> --extra-include-dirs=C:\\msys\\1.0\\local\\include
> --extra-lib-dirs=C:\\msys\\1.0\\local\\lib
I haven't built a binding for a while so I've forg
On 11 November 2010 18:01, C. McCann wrote:
> For instance, assuming serialize can be applied to functions of any
> type, it would probably be trivial to write a function (isExpr :: a ->
> Bool) that reports whether an arbitrary term is a primitive value or
> the result of some expression [SNIP]
On 11 November 2010 13:10, Lauri Alanko wrote:
>
> {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-}
>
> data PetOwner
> data FurnitureOwner
>
> data Cat = Cat { catOwner :: PetOwner }
> data Chair = Chair { chairOwner :: FurnitureOwner }
>
> class Owned a b | a -> b
On 11 November 2010 13:21, Nils Schweinsberg wrote:
>
> Is there an environment variable for this? As I said, I tried using
> --extra-include-dirs with MinGW\include.
I'm not sure about an environment variable. Adding the MinGW\ prefix
looks wrong, you may have to experiment with paths and forwa
Do you have the headers installed as well as the dlls?
For headers, MSys will have a search path of at least these two directories
msys\1.0\local\include
MinGW\include
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman
> If not Haskell, are there any languages which provide a simple serialization
> and deserialization of functions?
Napier88 was a persistent language that also had higher-order
functions. I've no experience other than reading about it but as its
persistence was "orthogonal persistence" I'd expect
Is it just me or does this bit in the proposal:
m .lookup key
.snd
.reverse
Which translates to this:
reverse . snd . (\m -> lookup m key) $ m
make no sense and refuse to type check - i.e lookup is producing a
Maybe not a pair for second?
I can see some benefit with TDNR for record
ut also the existence of each glyph in each font, one by
one, and will choose for each glyph the font that contains it."
So Browsers do know an awful lot about the installed fonts.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haske
Qualification is hardly verbose, idiomatically it tends to be two characters.
Qualification even with two chars is typographically ugly for infix functions.
Typographically, qualification is beyond the pale for infix _type
constructors_. It makes them very ugly and for many people type
signatures
You might want to consider SVG only as an output format.
As a graphics format it is very baroque with many special cases and
sundry obscure corners. If you like grand challenges, round-tripping
SVG might be interesting. Unfortunately this would likely consume all
the effort that you would otherwis
I'd use a parser combinator library that has word8 word16, word32
combinators. The latter should really have big and little endian
versions word16be, word16le, word32be, word32le.
Data.Binary should provide this and Attoparsec I think. Usually I roll
my own, but only because I had my own libraries
On 6 November 2010 18:01, Alexander Solla wrote:
>
> On Nov 6, 2010, at 3:56 AM, Stephen Tetley wrote:
>
>> Modern browsers might add in arrow from a different font if it is not
>> present in the one chosen by the web page author - I suspect this is
>> happening o
On 6 November 2010 09:52, Andrew Coppin wrote:
> I can't remember the last time I saw a browser that couldn't do this. There
> /are/ symbols that don't work reliably, but the basic arrow symbols seem to
> be pretty well supported.
Okay I'll shift my position a bit...
Arrows are likely present i
Hi Bulat
Doesn't your own FreeArc do pretty well? Its appealing to an audience
beyond programmers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 5 November 2010 21:31, Nick Bowler wrote:
> Except that the "Symbol" font family is not available in all browsers.
Ah ha - indeed you are right and the puritans at W3C and Mozilla.org
seem to have dug their heels in.
Unfortunately arrows don't appear to be in either the Standard Latin
Charac
On 5 November 2010 20:08, Andrew Coppin wrote:
> Would it be hard to replace "->" with a real Unicode arrow character?
>
It should be quite easy - whether a given font has an arrow readily
available is a different matter. It might be be simpler to drop into
the Symbol font (should be present for
ing, I'd contend that the bin-tree (aka a join-list)
has already taken the weight of the concatenation. To show a Hughes
list as efficient or inefficient a test would need to compare a plain
list and a Hughes list doing the concatenation themselves - the common
exemplar being string building
ZF Expressions (aka list comprehensions) date to at least David
Turner's KRC (St. Andrews Static Language) and Rod Burstall and John
Darlington's Hope c.1980. Maybe they were present in NPL, the
predecessor of Hope before that. The Hope paper nods to SETL as an
influence.
Without interviewing the
On 4 November 2010 12:03, Stephen Tetley wrote:
> Python is approximately as old as Python and most likely got
> indentation from ABC.
Apologies that should read - "as old as Haskell"
Obviously IDSWIM - (I _don't_ say what I mean).
___
Python is approximately as old as Python and most likely got
indentation from ABC.
Checking on Wikipedia, one of the ABC's creators was Lambert Meertens
(famous for *-morphisms amongst other things) so there is a lineage
going back to Algol and Peter Landin / ISWIM.
PS. my fact-checking is a bit
My familiarity with Python is a bit rusty, but the influence of
Haskell might be over-stated.
Type classes have gone from Haskell to Clean, Mercury (others?), and
monads have gone to F# but otherwise the functional features of the
current crop Python, Ruby etc. are not much different to what has l
Hipmunk is a bit of an oddity in that the Hackage package bundles the
original C library along with Haskell binding.
The first step would be to check that the C library has been built
properly - the build type in the cabal file is "Simple" but I don't
know if this would cause the C lib to be built
or boring old plain list to do
so well? More than just cons I hope.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Norman Ramsey has implemented Lua as an extension language for ML,
this included actually writing a Lua interpreter not FFI-ing to the
standard Lua. He has a series of good papers about the mechanics of
exposing the API of an application to the scripting language.
The code itself is available as p
See this conclusion of this thread - installing the latest version
from Hackage seems to be the solution:
http://www.haskell.org/pipermail/haskell-cafe/2010-August/082141.html
Note that although regex-posix is a binding to a C library, because
the library and headers are delivered with the Platfo
x27;t seem to have any
connection to a notion "difference".
Best wishes
Stephen
* It seems from other commentators on the thread that Haskell Hughes
lists are actually different from Prolog difference lists anyway.
___
Haskell-Cafe mailing list
H
On 31 October 2010 16:53, Nils Schweinsberg wrote:
> Am 31.10.2010 17:27, schrieb Stephen Tetley:
>>
>> Left factoring! :-)
>
> Stupid question: Whats that? :)
>
Actually a good question...
Its a standard grammar transformation - if you have two alternative
product
On 31 October 2010 16:23, Ozgur Akgun wrote:
> Am I missing something?
Left factoring! :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 31 October 2010 15:55, Stephen Tetley wrote:
ecessary.
>
> You can also write separate parsers this is covered in the (pdf)
> Parsec manual available from Daan Leijen's old home page, however I
> usually avoid this as it seems rather cumbersome.
D'oh. I meant "sep
If you use the Language and Token modules, Parsec gives you something
close to a lexer / parser separation _but_ you can drop down to
character level parsers if you want to - this is very handy. There are
some caveats though - for instance, the number parsers from the Token
module follow Haskell's
Possibly related to this bug?
http://trac.haskell.org/haskell-platform/ticket/137
http://www.haskell.org/pipermail/haskell-cafe/2010-August/082141.html
I don't use cabal install, but maybe you could try just re-installing
regex-posix, then once its working reinstall the dependencies. That
seemed
On 30 October 2010 11:07, Henning Thielemann
wrote:
> Looks like you are about to re-implement numeric-prelude. :-)
Ah, but Numeric-Prelude is huge though[*].
DavidA complains in the recent Cafe thread "Decoupling type classes
(e.g. Applicative)?" that the Num hierarchy can't be replaced due t
2010/10/29 Dupont Corentin :
> Also, I can't manage to write the more generic function SB x -> SA x.
>
Horribly enough this one seems to work...
mapOnBofA :: SB a -> SA a
mapOnBofA mf = get >>= \st@(A {b=temp}) ->
let (ans,temp2) = runState mf temp
in put (st { b=t
On 28 October 2010 20:59, Don Stewart wrote:
>
> "Status of Infrastructure" questions like this are best asked on the
> Haskell Reddit.
[SNIP]
> P.S. I encourage people to use the online forums: Haskell Reddit and Stack
> Overflow, as a lot of the question-answering activity has shifted there
>
On 27 October 2010 09:32, Ivan Lazar Miljenovic
wrote:
> Why not write your own Pretty class for that project then?
Personally I don't like type classes if they're solely for notational
convenience. I want them to be a least a convention and its nicer
still when they genuinely represent somethin
On 27 October 2010 08:57, Ivan Lazar Miljenovic
wrote:
>
> What do you mean by "prettyExpr"?
Without a type class I generally name pretty printers by the pretty
'pretty' then the type they print Expr (expression), Decl
(declaration) etc.
> My main objection to having a Pretty type class is that
On 27 October 2010 00:21, Richard O'Keefe wrote:
> Here's the table of contents of a typical 1st year discrete mathematics book,
> selected and edited:
> - algorithms on integers
> - sets
> - functions
> - relations
> - sequences
> - propositional logic
>
e hex printers anyway, so one size via a type class
doesn't fit all. As for the class - if I have a reasonably sized
syntax tree I'd rather just do
> pretty a
... than formulate a naming scheme like:
> prettyExpr a
Regards
Stephen
___
Hask
The lexer was wrong - but it was the lexer function not the lexer spec
- try the one below.
Note that you have to take 'len' chars from the original input.
Previously you were taking the whole of the "rest-of--input":
lexer :: (TheToken -> P a) -> P a
lexer f input@(_,_,instr) =
case alexScan i
gt;>= print . alexScanTokens
Note - your sample file is using extended characters so it fails for
me with Alex 2.3.2. I'm now sure how capable the current version of
Alex is or whether better Unicode support can be enabled with flags.
Regards
Stephen
___
On 25 October 2010 22:10, Andrew Coppin wrote:
>
> If I were to somehow obtain this book, would it actually make any sense
> whatsoever? I've read too many maths books which assume you already know
> truckloads of stuff, and utterly fail to make sense until you do. (Also,
> being a somewhat famous
On Wed, Oct 20, 2010 at 4:27 PM, Stephen Sinclair wrote:
> On Wed, Oct 20, 2010 at 3:11 PM, Stephen Tetley
> wrote:
>> Claus Reinke posted this a while ago - see the attachment at the
>> bottom of the message:
>>
>> http://www.haskell.org/pipermail/haskell-cafe/20
On Wed, Oct 20, 2010 at 3:11 PM, Stephen Tetley
wrote:
> Claus Reinke posted this a while ago - see the attachment at the
> bottom of the message:
>
> http://www.haskell.org/pipermail/haskell-cafe/2007-July/029275.html
Thanks for that. Here's the relevant website that he pos
Claus Reinke posted this a while ago - see the attachment at the
bottom of the message:
http://www.haskell.org/pipermail/haskell-cafe/2007-July/029275.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/has
On 20 October 2010 12:30, John Lato wrote:
[SNIP]
> Again, "Tool Authoring" is too broad to be useful.
Who are the skills lists for?
Recruiters, other Haskellers to form "strike forces", something else?
For the recruiters I think they are somewhat obscure unless Well-Typed
or Galois were search
On 18 October 2010 21:03, wrote:
[SNIP]
> I'm happy to hack and update, but is there any way of finding
> out which modules depend on QuickCheck rather than going through each file
> one by one?
grep for "QuickCheck"? - any module that uses it will need it in the
import list.
__
#x27;s notation is too general for my purposes in this case. Conal
encodes a "path" directing what the lifted function operates on as
part of each "editor", because my "paths" are shorter and I have fewer
of them I'd prefer to encode them directly as named combinators.
Thanks again
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
The avoiding /try/ is a good part of Parsec golf. Because turning
natural literals into fractions is easy (%1) it is simple to use the
/option/ parser to parse a suffix or return a default.
/symbol/ is also a valuable parser, often preferable to /char/ or
/string/ as it chomps trailing white space
work looking at sets of combinators for these
higher arity functions - papers or code? I'd prefer not to introduce a
whole new lexicon of combinator names if I can help it.
Thanks
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 16 October 2010 09:02, Stephen Tetley wrote:
> On the main topic - I think the blurb is fine. If Python and Ruby want
> to do proselytization and value judgements please leave them to it.
PS - Were it me, I would drop the third sentence of the Haskell.org
blurb, to me it is a value jud
h my interest.
On the main topic - I think the blurb is fine. If Python and Ruby want
to do proselytization and value judgements please leave them to it.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 14 October 2010 10:15, Jacek Generowicz wrote:
> [Gregory: Sorry about duplicate, accidentally took it off-list.]
>
>> On 2010 Oct 14, at 09:46, Gregory Collins wrote:
>> There is more information about the different ways of doing this kind of
>> thing in Haskell in the OOHaskell paper:
>> http
Hi Jonas
Thanks - I was anticipating a type like this for the destructor:
viewl :: Finite s a -> Either () (a, Finite (Predecessor s) a)
I didn't appreciate that the size type in your code represented the
upper bound and not the actual size.
Best wishes
t wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi Jonas
Nice, but how about a list destructor?
;-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 12 October 2010 14:08, Jacek Generowicz wrote:
> Reading the GHC docs on Data.Dynamic, I infer that Data.Dynamic is
> non-standard, but, in principle, portable to other implementations.
>
> Is that understanding correct?
Yes - Data.Dynamic uses some GHC specifics but there are other
"lightwei
To do this I would use dynamic types (via Data.Dynamic).
There are more typeful ways to deal with heterogeneous structures[*],
but if "clients can easily extend it with their own new types" you've
pretty much defined what dynamic types solve.
[*] See the HList papers and library and various solu
lication with (#) gave
code a nice OO-like reading.
The other was Peter Thiemann's Wash - (#) is again flip ($) and (##)
is flipped compose.
Typographically I think these are a good fit, unfortunately they now
might play badly with GHC's magic hash operator.
Best wishes
Stephen
2010/10/10 André Batista Martins :
[Snip]
>
> I think that work has been done, in helium compiler. But i can't identify
> the algorithm for this propose.
>
It may be a "hand written" hint that generates the very precise help
"probable fix : re-order arguments".
See the paper "Scripting the Type
On 10 October 2010 11:31, C K Kashyap wrote:
> Did you mean this
> http://www.cs.tufts.edu/~nr/comp150fp/archive/richard-bird/sudoku.pdf?
I was actually meaning these slides...
http://icfp06.cs.uchicago.edu/bird-talk.pdf
> Also, is this the book -
> http://www.flipkart.com/pearls-functional-al
ordin and Andrew Tolmach - Modular Lazy Search for Constraint
Satisfaction Problems
http://web.cecs.pdx.edu/~apt/jfp01.ps
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Apologies -- I was running a wrong snippet. Mark is working correctly,
I'll have another look...
On 10 October 2010 09:15, Stephen Tetley wrote:
> Isn't mark is always increasing the size of the board? - I haven't run
> the code but I if this is the behaviour you want '
Isn't mark is always increasing the size of the board? - I haven't run
the code but I if this is the behaviour you want 'mark' is probably
not a good name (I'd expect mark to be returning something the same
size but with marked elements).
In _mark_ the before and after are always splits, so the co
Of related interest, there have been more recent papers by the Clean
developers on "Arrow GECS" and iData but they are about Clean where
this is no IO monad.
Maybe Haskell cannot be liberated from IO after all...
___
Haskell-Cafe mailing list
Haskell-Caf
Maybe Peter Ljunglöf's thesis will be useful?
http://www.ling.gu.se/~peb/pubs.html
http://www.ling.gu.se/~peb/pubs/Ljunglof-2002a.pdf
It covers chart, GLR and CYK parsing - isn't Earley's parsing method
related to either chart or CYK?
___
Haskell-Cafe m
nenberg's Nyquist generates
UGens in this way from a Scheme like macro language, but its a long
time since I looked at it.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hello John
If you are wanting variables, lambdas ... it sounds like you might be
"off-shoring" - i.e. building a little language within Haskell that is
executed on something else GPU (compiled to CUDA), compiled to C,
compiled to VHDL, etc.
Generally this is a "deep-embedding" as you need to prod
Does this one give the "expected" error message for Parsec3.1 -
unfortunately I can't test as I'm still using Parsec 2.1.0.1.
> parser = block (many digit "digit")
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/lis
On 25 September 2010 05:30, Evan Laforge wrote:
> I thought the parsec source included some example parsers for simple
> languages? In any case, there is lots of material floating around,
> [Snip]
The best documentation is Daan Leijen's original manual, plus the
original source distribution wh
o some way towards this (although I think the book aims at something
rather different - developing elegant algorithms - "pearls", rather
than program design per se).
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Sun, Sep 19, 2010 at 3:51 PM, Karel Gardas wrote:
>
> Hello,
>
> from time to time request for Haskell running on top of Java's VM pops
> on the haskell related mailing list and then usually dies off when
> someone mentions that JDK does not have proper support for tail-calls. I
> think haskell
On 15 September 2010 16:29, Matias Eyzaguirre wrote:
> Secondly, (and more importantly, or at least more interesting) I can see how
> one would make a generator for simple compound data types, but how on earth
> do you make a generator produce
> functions?__
On 11 September 2010 20:45, Henning Thielemann
wrote:
> It uses the Applicative instance for functions.
Yep - I meant that, but somehow didn't write it, then pressed the send button...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.h
On 11 September 2010 18:21, Jonathan Geddes wrote:
>>someUpdate :: MyRecord -> MyRecord
>>someUpdate myRecord = myRecord
>> { field1 = f $ field1 myRecord
>> , field2 = g $ field2 myRecord
>> , field3 = h $ filed3 myRecord
>> }
Applicatively, using no additional libraries, is how
of interest and convert after
parsing to a smaller typed tree (with only the syntax you are
interested in).
By the way, HaXML has has a tool called DTD2HS (I think) that will
generate Haskell datatypes from a DTD definition.
Best wishes
Stephen
___
ackage
creates it when you upload?
Category: Embedded
This is a bit prone to spam I suppose, but could be even worse for bad
spellers (like myself). Even at the moment, there seems to be some
discrepancy between categories named with the plural or the singular.
On 10 September 2010 07:14, Mitar wrote:
> But I am not sure how. Because now compiler, for example, warns me of
> a non-exhaustive pattern even if some MaybePacket value is not
> possible for given Line.
This issue pops up quite quite often - Ryan Ingram's answer to it the
last time it was on t
Hi Günther
You might want to look at Samuel Kamin's work in the first instance.
This was later extended by Conal Elliott and others to use typed
representations (i.e. abstract syntax) - Samuel Kamin used
quasi-quoted Strings.
http://loome.cs.uiuc.edu/pubs.html
Particularly these two:
http://loom
201 - 300 of 673 matches
Mail list logo