On 22 July 2011 16:32, Johannes Waldmann wrote:
> Stephen Tetley gmail.com> writes:
>
>> "Compilers: Principles, Techniques, and Tools" by Aho et al. though
>> the presentation in this book is quite formal.
>
> you make that sound like a bad thing ...
As Haskell is statically typed, if y.length < 100, y is still of type Big...
On 22 July 2011 10:18, Patrick Browne wrote:
> 2) Assert the type of a variable
> e.g. if y.length > 100 then y is of type big.
___
Haskell-Cafe mailing list
Haskell-Cafe@has
algorithms varies considerably.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 17 July 2011 10:03, Patrick Browne wrote:
> Question 1: Is the above a reasonable understanding of CD?
>From a brief look, constructor discipline (CD) restricts left-hand
sides of equations to have no function calls themselves.
http://users.dsic.upv.es/~gvidal/german/pepm97/paper.pdf
__
This seems to be a general problem with the Hackage server as other
packages uploaded after yours have failed to build with similar
errors...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Or Andy Gill's Dotgen - simple and stable:
http://hackage.haskell.org/package/dotgen
On 22 June 2011 16:16, Vo Minh Thu wrote:
>
> See the graphviz package: http://hackage.haskell.org/package/graphviz
___
Haskell-Cafe mailing list
Haskell-Cafe@haske
How fast is good old String rather than ByteString?
For lexing, String is a good fit (cheap deconstruction at the head /
front). For your particular case, maybe it loses due to the large file
size, maybe it doesn't...
___
Haskell-Cafe mailing list
Haske
On 22 June 2011 05:30, Arnaud Bailly wrote:
> Are there works/thesis/books/articles/blogs that try to use Cat.
> theory explicitly as a tool/language for designing software (not as an
> underlying formalisation or semantics)? Is the question even
> meaningful?
You might find Don Batory (U. Texas
On 15 June 2011 13:38, Gregory Guthrie wrote:
> ---
>> Subject: Re: [Haskell-cafe] Best platform for development with GHC?
>> On Wed, 15 Jun 2011, Dmitri O.Kondratiev wrote:
>>
>> Since I maintain the gnuplot binding for Haskell - what are the particular
>>
On 9 June 2011 09:02, Yves Parès wrote:
> Were templates an original feature of C++ or did they appear in a revision
> of the langage ?
> Because C++ appeared in 1982 and Haskell in 1990.
Templates were a later addition to C++. There is a strong tradition of
generics in OO and related languages t
Hi Lyndon
Are you just coalescing adjacent elements (if they are the same constructor)?
As it seems you have a list here rather than a tree, I'd step out of
Uniplate at this point and just do a list traversal with direct
recursion.
___
Haskell-Cafe mai
On 5 June 2011 20:20, Vo Minh Thu wrote:
> One thing that would be neat for you, but I have no idea if it exists,
> would be to turn directly the CSG models to 2d vector graphics.
>
I don't know if it is CSG, but in the TeX world there is Gene
Ressler's 3D modelling program Sketch that generates
On 4 June 2011 10:42, Tillmann Vogt wrote:
> Well, what is the difference between a tag and a category? The second sounds
> more mathematical.
Although it doesn't exist (yet), tags would support a filtering view.
As for categories, I'll be the first to play the joker and mention the
essay "Ontol
2011/5/31 Scott Lawrence :
> Evaluation here also doesn't terminate (or, (head $ unfoldM (return .
> head)) doesn't), although I can't figure out why. fmap shouldn't need to
> fully evaluate a list to prepend an element, right?
I'm afriad fmap doesn't get to choose - if the monad is strict then
b
On 30 May 2011 05:27, Anupam Jain wrote:
> Why doesn't Haskell have built in syntactic sugar for atoms?
Because they don't have a functional interpretation? (i.e. they're
really a hack)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www
nformation
Flow Security Through Precise Control of Effects" and "Domain
Separation by Construction".
http://people.cs.missouri.edu/~harrisonwl/publications.html
On 29 May 2011 22:06, Yves Parès wrote:
> @Stephen: Resumption monads? It looks interesting, but I fait
On 27 May 2011 20:06, Yves Parès wrote:
> So I thought about Arrows, as they can express sequential and parallel
> actions, but I don't know if it would be a right way to model the
> interruptions/recoveries.
> What do you think about it? Do you know of similar situations and of the way
> they've
t of
type system power to get over the representation mismatch between
trees and tables.
Wolfram Kahl - Compositional Syntax and Semantics of Tables
http://www.cas.mcmaster.ca/sqrl/papers/sqrl15.pdf
Best wishes
Stephen
___
Haskell-Cafe mailing list
advantage on the state-of-practice that would counter
balance its position as a marginal language. There are good reasons
why enterprise development is conservative, state-of-the-art languages
like Haskell or Erlang excel in domains where they can be disrupti
Hi Ivan
empty is fine as is, obviously with a Monoid instance as well, people
can choose to use mempty which removes potential name clashes.
I was thinking of (<$>) and (<+>), though I was forgetting that (<+>)
is actually ArrowPlus.
If you are mostly gifting angles as notation to Applicative, m
Hi Ivan
Forks are good, no?
The Parsec experience has suggested to me at least, that new author's
"capping" another author's work by bumping up to a major version,
causes a significant difficulties even when the original author has
gone.
As for wl-pprint, it was a very tidy library in its origin
On 24 May 2011 13:41, Johannes Waldmann wrote:
> I could just store the length of the list - as an additional argument
> to the "Cons" constructor that is automatically initialized on construction
> (and you never need to change it later, since Haskell objects
> are "immutable", in the words of J
Form Hackage it looks as though the module MissingH.List no longer
exists in the MissingH package - note the linked article is from 2005.
What is the code you are trying to compile?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haske
On 19 May 2011 21:20, Andrew Coppin wrote:
> This is about all those people who think having multiple libraries which
> only solve half the problem is somehow a "good thing".
Och (number 2)
Those people are the Straw Men - you can wave at them from your car
window when you pass them as they sta
Och Mr Coppin
Lisp is a fine language, but all "Lisp" essays you'll find on the
internet except Richard Gabriel's "Worse is Better" are absolute tosh.
Read Olin Shiver's introduction to SRE regex notation for an
intelligent contribution to the "6 different libraries" problem you
seem to be having
On 18 May 2011 19:25, Tom Murphy wrote:
> I'd give three reasons for disagreeing:
> 1. Developing a complete GUI has been a low priority up until now,
...
I don't think that not having something as desireable good GUI suited
anyone much, nor has it actually been a low priority - a lot of work
ha
Cool.
On 17 May 2011 16:42, Brent Yorgey wrote:
> - Create a higher-level module built on top of the diagrams framework
> (e.g. tree or graph layout, generating Turing machine configuration
> diagrams, Penrose tilings ... your imagination is the only limit!)
> and submit it for inclus
The hashtable needs to be been created in IO, after that, think of the
'hashtable' as a analogous to a file handle. You have to pass it
around to do anything with it - but the only things you can do with it
are in IO.
(That's why no-one really likes it, of course...)
_
It looks like cabal-install is wanting to do wacky things to the GHC
boot libraries, which means something is seriously astray.
What happens when you run `ghc-pkg check` ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mai
On 8 May 2011 06:14, Nicholas Tung wrote:
> Dear all,
> I'd like to write a function "maybeShow :: a -> Maybe String", which
> runs "show" if its argument is of class Show.
I'm pretty sure this is not readily possible - there might be some
hack through Typeable but that would oblige but Show
"show" is the failing package
A look on Hackage suggests that "show" had problems with its cabal
file at versions 0.4 & 0.4.1 and was fixed at 0.4.1.1.
Can you try installing "show" individually at 0.4.1.1 the try
installing the rest of lambdabot.
___
On 3 May 2011 13:26, Yitzchak Gale wrote:
>> Both are "kind of, sort of" bringing you up to a Monoid though...
>
> altconcat and sconcatMaybe are doing that, because you
> need to decide what to do with an empty list when you
> define the instance. Holger's interface is not doing that,
> because
There is that formulation, though usually I find I need to do it with
an alternative instead:
altconcat alt [] = alt
altconcat _ (a:as) = go a as
where
go acc [] = acc
go acc (b:bs) = go (acc <> b) bs
Both are "kind of, sort of" bringing you up to a Monoid though...
On 3 May 201
Does it have an obvious default implementation, bearing in mind it we
might really want a total function?
sconcat [] = error "Yikes - I wish this was total!"
sconcat [a]= a
sconcat (a:as) = a <> sconcat as
Best wishes
Stephen
On 3 May 2011 12:12, Yitzchak Gale wrote:
On 27 April 2011 21:28, Alexander Solla wrote:
>
> On Wed, Apr 27, 2011 at 11:16 AM, John Obbele wrote:
>>
>> Second issue, I would like to find a way to dispatch parsers. I'm
>> not very good at expressing my problem in english, so I will use
>> another code example:
>
> This sounds very hard i
John Meacham's DrIFT tool used to get extended faster than GHC for
things that "should" be automatic. I'm not sure of its current status,
though:
http://repetae.net/computer/haskell/DrIFT/
For your second problem, something like this:
getAB :: Get (Either A B)
getAB = do
len <- getWord16be
ure "mean what they" say so only
only my second definition is allowed, the first version won't compile.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Surely `fromChunks` is making the both lines in the code snippet the same?
Also, in your last sentence I think you've miscalculated the shape of
the initial input.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
t; m ()
For practical purposes I've found STArray's a bit of a white elephant
- I always use IOArray instead, as I've either needed to initially
read an array from file or write one to file at the end. You can't do
this with ST.
Best wishes
Stephen
__
.
These days I do like all lower case for variables though (unless the
variables are functions and need better names than f g or fn).
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
Hi Albert
You could try benchmarking with DeltaML instead - DeltaML is the only
language I can think of where memoization is (nearly) pervasive,
though you need still need to mark memo functions with a keyword as
far as I'm aware. This would be a lot easier than modifying GHC:
http://www.mpi-sws.
retty substantial undertaking. In the first instance where
do you put the memo-ed values? - if you're doing it for all functions
you might have to change the RTS as well as the compiler.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Ha
ert
There isn't much value to automatic memoization as people have already
pointed out on SO - if you believe otherwise, you're probably better
off proving a case on paper first before attempting to implement it in
GHC.
Best wishes
Stephen
27;d be looking to
solve.
There was a thread on Haskell Cafe about them last November called
"Making monadic code more concise", that you might find interesting -
especially Oleg Kiselyov's comments:
http://www.haskell.org/pipermail/haskel
to fairly standard
combinators on functions. But they generalize the combinators to
operate on other types than the function type (->). As there isn't a
relation between input and output, I don't quite see how the Stream
type could start as a combinator.
Best wishes
Stephen
___
operator
names will be familiar to other programmers.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
. Naturally, I'm not suggesting that you should agree with
my analysis - but I would flag a caution that FreeType is very
problematic to bind to.
The abandoned code is in Copperbox:
http://code.google.com/p/copperbox/source/checkout
path in the trunk: libs/graphics/FreeType
Best wishes
St
es some errors
mentioning Edge - as Edge is one of the instances of SubUnit, I think
the function body is less polymorphic than you expect.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi Edgar
On 26 March 2011 20:19, Stephen Tetley wrote:
> ... you
> want to use scoped type variables so that the local type annotation is
> *the same type* type variable.
Ahem ...
> so that the local type annotation is *the same type variable*.
Where is Data.Vec coming from so
ature, you
want to use scoped type variables so that the local type annotation is
*the same type* type variable.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
For the specific error at line 265 I think you should be using
ScopedTypeVariables and properly qualifying the type signature at the
function level with a forall.
The local annotation { ::(SubUnit a)=> } is presumably introducing
another type variable unrelated to 'a' in the function level type
si
On 23 March 2011 10:28, C K Kashyap wrote:
> I am not able to ascertain if what you are saying is consistent with
> http://www.haskell.org/haskellwiki/Embedded_domain_specific_language
> Regards,
> Kashyap
Well - I'm not sure if the description of a shallow embedding on that
page is particular
A shallow embedding would typically use just functions - a famous
example is Paul Hudak's "region server". A deep embedding would build
syntax - represented with data types - and interpret the syntax or
compile the syntax for another use (so called "off-shoring" e.g. Conal
Elliott's Pan).
Andy Gill uses a monad in his Dot library to allow graphs to have
references as they are built. It's a pattern I like a lot and has been
very useful for my graphics kit Wumpus.
That said, while it's a good technique for graphs, its use is more
equivocal for trees where nesting is more prominent. I
If you get the old Parsec distribution from Daan Leijen's home page
there are example parsers for Henk a small functional language and I
think Mondrian (a bit large one).
http://legacy.cs.uu.nl/daan/parsec.html
___
Haskell-Cafe mailing list
Haskell-Cafe
On 18 March 2011 13:31, Grigory Sarnitskiy wrote:
> Anyway, a new question arose. If I have already declared a type, can I add
> new constructors to it from other modules?
>
> Maybe there are some GHC extensions to solve both these problems.
"no can do".
There are ways to encode extensible ty
I haven't tried myself - but from the docs, partial parsers seem to
depend on finding an error token so they seem to be partial as in
"handles failure".
If you want to parse specific fragments you probably want to generate
multiple parsers from a single grammar see section 2.7.
__
e outer_comment defs = Module outer_comment fake_name defs
> where
> fake_name = "ERR - parser error reading module name"
>
Ideally the smart constructors should be in a monad that supports
error logging like Writer.
As you can see this isn't a great way of doing
ar is the main tool you have.
On 8 March 2011 15:54, Stephen Tetley wrote:
> I'd join comments in with tokens so each token has a comment -
> possibly the empty string, then the parser can decide what to do with
> the comment part of token - e.g retaining it for functions, ignoring
I'd join comments in with tokens so each token has a comment -
possibly the empty string, then the parser can decide what to do with
the comment part of token - e.g retaining it for functions, ignoring
it for everything else.
You may have to write a two-pass lexer to do this.
ec.html
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
There's also Martin Erwig's Parametric Fortran - which looks largely
similar but hides some of the parametric types with existentials.
Check the papers on his website, epscially the PADL one:
http://web.engr.oregonstate.edu/~erwig/papers/abstracts.html
___
y
to backtrack.
On 2 March 2011 16:24, Stephen Tetley wrote:
>
> *try* means backtrack on failure, and try the next parser. So if you
> want ill formed strings to throw an error if they aren't properly
> enclosed in double quotes don't use try.
Apologies if this has been answered already (I've got a bit lost with
this thread), but the *try* here seems to be giving you precisely the
behaviour you don't want.
*try* means backtrack on failure, and try the next parser. So if you
want ill formed strings to throw an error if they aren't proper
Maybe you've invented the ApoPrelude?
If I were doing it I'd probably code them in terms of an apomorphism -
unfoldr with flush. Unlike regular unfoldr which discards the final
state, an apomorphism uses the final state to produce the tail of the
output list. See Jeremy Gibbons paper "Streaming
re
I think FTGL is the only option. Where did you have the setup problems
- with the C libraries (FreeType and FTGL) or the Haskell binding to
FTGL?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Does this help?
listbind :: [a] -> (a -> [b]) -> [b]
listbind = (>>=)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
.1.19.8983
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi wren
Thanks for that explanation - it's by far the clearest description of
iteratees / enumerators I've seen.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 25 February 2011 20:38, wrote:
> The short version is that I think there is a more enlightening view of
> iteratees than as a kind of a fold. For me, it makes a lot more sense to
> think of them as operations in a particular abstract monad which has one
> associated operation, a blocking rea
On 23 February 2011 15:40, Kurt Stutsman wrote:
> instance Enum e => Serializable e where
> get mask = {- convert mask to Int and then to a BitSet -}
> put bitset = {- convert BitSet to Int and then to String -}
>
I looks like all you need is for objects to be enumerable, i.e have
instances
On 23 February 2011 05:31, Johan Tibell wrote:
> Can someone come up with a real world example where O(1) size is important?
>
Tangentially - if you changed the API so the size function was called
'count' rather than 'size' or 'length', there would be no shame what's
so ever in not being O(1).
On 22 February 2011 13:19, Yves Parès wrote:
> Concerning game development in Haskell, I would be most interested in
> an article explaining one (or several) game architectures in Haskell,
> i.e. how do you design the high layers of your game to take the most
> of Haskell features : threads, monad
The finally tagless and "Generics as a Library" styles can - though
you loose pattern matching they are arguably still close to grammars.
Pablo Nogueira has posted some examples of open types in "Generics as
a Library" tagless style to Haskell cafe:
http://www.haskell.org/pipermail/haskell-cafe/2
On 16 February 2011 15:31, Roman Dzvinkovsky wrote:
>
> using alex+happy, how could I parse lines like these?
>
>> "mr says \n"
Alex has both user states and powerful regex and character set
operators (complement and set difference), that said, LR parsing plus
Alex lexing doesn't look like a sa
Might better ways, but the following work:
length [c | x <- [1..100], let c = chain x , length c > 15]
length [c | x <- [1..100], c <- [chain x] , length c > 15]
On Wed, Feb 16, 2011 at 9:19 AM, Tako Schotanus wrote:
> Hello,
>
> I was going through some of the tuturials and trying out differe
Is pkg-config available for MSys? It might help matters if it is - I
think Cabal has direct support for pkg-config.
Otherwise point Cabal to the location of the .a file with
--extra-lib-dirs. You will also have to point to the headers with
--extra-include-dirs.
If you are compiling with GHC strai
Maybe the Zord64_HARD.lhs is at fault for not using qualified module
names? I can't see why this would be the case though, but at look at
the source shows it doesn't.
In future, please could you put some information about your problem **
at the top ** of your message rather than burying it many li
On 9 February 2011 23:35, Dan Knapp wrote:
[SNIP]
> I believe this means that if we have a
> package named "hs-save-the-whales" that is under the GPL, and a
> front-end package "hs-redeem-them-for-valuable-cash-prizes" which
> makes use of the functionality in hs-save-the-whales, the front-end
>
On 7 February 2011 10:16, Jimbo Massive wrote:
> It's often struck me that, this information is clearly part of the
> interface to a function, given that correct operation of calls to that
> function may depend on it, yet we (implicitly) pretend that it's not (by
> rarely documenting it).
>
> Wou
On 6 February 2011 19:41, Andrew Coppin wrote:
. (E.g., the
> compiler can't even determine whether a binding is recursive or not for
> itself. You have to say that manually.) It seems a very unecessarily
> complicated and messy language - which makes the name rather ironic.
Erm - nope. Sure you
On 1 February 2011 12:45, Ozgur Akgun wrote:
> I am not very much interested in the technical details about how things
> currently are, I am more interested in a discussion about why (if?) this
> would be considered a design flaw?
Wanting a general base case + specific exceptional cases is in no
On 1 February 2011 11:47, Ozgur Akgun wrote:
>
> So, is there a way to declare an AbGroup instance for the types with num
> instances only?
No - as Henning says its then no more useful than simply a function:
add :: (Num u) => a -> a -> a
add = (+)
'Overarching instances' i.e. classes with one
ok to concentrate more on music - I think he's making
drafts available.
If you have Haskore specific queries, the Haskell-art list is better
than Cafe as Paul is a regular commentator there.
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 27 January 2011 15:04, Chris Smith wrote:
[SNIP]
> I'm wondering if anyone has
> experience in anything similar that they might share with me. I'm
> trying to decide if this is feasible, or it I should try to do something
> different.
Hi Chris
John Peterson had some nice work using Haskore a
On 24 January 2011 02:02, Daniel Fischer
wrote:
> You can try with hslogger-1.1.0, which built on 6.12 and 7.0 on hackage, or
> maybe with hslogger-1.1.2 (which hasn't yet been built on hackage since it
> was uploaded only yesterday).
> hslogger-1.1.1 had the same build failure on hackage.
Isn't
I don't think you can do this "simply" as you think you would always
have to build a parse tree. If the input is valid Haskell you could
follow Chung-chieh Shan's suggestion, otherwise you could parse to a
"skeleton syntax tree" - look for work by Jonathan Bacharach on Dylan
macros and "Java Syntax
ishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 12 January 2011 06:57, Patrick Hurst wrote:
> Is it just me, or is HXT slow? I noticed that both reading a document
> from a file, as well as running computations, are exceedingly slow,
> with simple stuff like 'get the contents of everything with a given
> class' taking .3 seconds for a 400KB
ion.
http://conal.net/papers/data-driven/paper.pdf
Best wishes
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
You have two choices (other people have enumerated the first while I
was typing):
First choice:
Wrap your Stringlist with a newtype:
newtype StringList = StringList [String]
The downside of this your code gets "polluted" with the newtype.
Second choice:
Write special putStringList and getStri
write things like:
>
>> bad_ones :: Stream Int
>> bad_ones = s where s = 1 `S.cons` s
>
> ...
Thanks Duncan and Henning again ealier.
I'll see if I can do without tight, circular definitions or change to
an inductive stream representation if I f
uld like to know whether of not this is impossible with
Stream-Fusion anyway.
Thanks again.
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
; bad_loopy :: [Int]
> bad_loopy = S.append1 (S.take 10 v) []
> where
> v = 1 `S.cons` v
> good_productive :: [Int]
> good_productive = S.append1 (S.take 10 v) []
> where
> v = S.repeat 1
Thanks
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
included a rationale for
the merits of there golfing, rather than just the obfuscated code.
Happy New Year to all.
Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On 28 December 2010 21:44, Edward Amsden wrote:
[SNIP]
> I'm writing a very similar library to Yampa. (I would be patching
> Yampa, but the code is a mess, so I decided to try starting from
> scratch.)
> Basically, I have a signal processing loop, where values are passed
> updated with a Maybe, r
On 28 December 2010 19:23, Edward Amsden wrote:
> Hello all:
>
> I'd like to right a function that could take a structure with type
> (random example):
>
> (Int, (String, (Int, Int)))
>
> and another where each individual value is a Maybe of the
> corresponding type, for example:
> (Maybe Int, (Ma
On 27 December 2010 07:35, Jonathan Geddes wrote:
> #1 Parse a string at compile-time so that a custom syntax for
> representing data can be used. At the extreme, this "data" might even
> be an EDSL.
Hello Jonathan
By this are you meaning to add quasiquoting to the language "Haskell"
or the "G
> instance Monad m => MonadPlus (MaybeT m) where
> mzero = MaybeT $ return Nothing
> mplus x y = MaybeT $ do maybe_value <- runMaybeT x
> case maybe_value of
> Nothing-> runMaybeT y
> Just
On 26 December 2010 19:00, michael rice wrote:
>
> I lifted the code below from here:
>
> http://en.wikibooks.org/wiki/Haskell/Monad_transformers
>
> Since the wiki page doesn't say what needs to be imported, I'm guessing.
>
> Not sure what is happening. Maybe someone can tell me.
> instance Mona
101 - 200 of 673 matches
Mail list logo