On 2/22/08, Taral <[EMAIL PROTECTED]> wrote:
> shift :: Prompt r -> ((a -> _) -> r) -> a
>
> (Where _ is either r or forall b. b)
It occurs to me that _ has to be r, otherwise the subcontinuation can escape.
--
Taral <[EMAIL PROTECTED]>
"Please let me know if there's any further trouble I can
On Fri, 2008-02-22 at 19:04 -0800, Taral wrote:
> On 2/22/08, Derek Elkins <[EMAIL PROTECTED]> wrote:
> > shift and reset
>
> I was under the impression that reset was a pure function. What side
> effects does it have?
It depends on how you define "pure function". It's not particularly
relevant
On 2/22/08, Derek Elkins <[EMAIL PROTECTED]> wrote:
> shift and reset
I was under the impression that reset was a pure function. What side
effects does it have?
--
Taral <[EMAIL PROTECTED]>
"Please let me know if there's any further trouble I can give you."
-- Unknown
___
On Sat, 2008-02-23 at 01:28 +, Duncan Coutts wrote:
> Basically I'd like to know what tool (that is packaged on every linux
> distro) do I use to convert a docbook .xml file to xhtml. I took a quick
> look on the FAQ linked from docbook.org/help and could not immediately
> find what standard
On Fri, 2008-02-22 at 07:21 -0800, Keith Fahlgren wrote:
> On 2/21/08 3:57 PM, Duncan Coutts wrote:
> > Consequently there is no support in
> > Cabal etc for those kinds of documentation. GHC, Cabal and c2hs amongst
> > others use docbook but it's a horrible format to write and the tools to
> > pr
Mark P Jones wrote:
> Ben Franksen wrote:
>> TREX seems to be generally agreed to be too complicated to implement and
>> explain.
>
> What evidence do you have for this?
Not much, I have to admit that. It basically seems to be SPJ's opinion, as
he writes in his proposal that he "never got around
On Fri, 2008-02-22 at 15:13 -0800, Taral wrote:
> On 2/22/08, Derek Elkins <[EMAIL PROTECTED]> wrote:
> > Nothing but sanity is stopping you. If you make a new language, you can
> > do whatever you like. However, with shift and reset you can represent
> > any effect, so you would utterly lose p
On 2/22/08, Derek Elkins <[EMAIL PROTECTED]> wrote:
> Nothing but sanity is stopping you. If you make a new language, you can
> do whatever you like. However, with shift and reset you can represent
> any effect, so you would utterly lose purity.
Can you give an example of an impure function cr
On Fri, 2008-02-22 at 14:27 -0800, Taral wrote:
> On 2/22/08, Taral <[EMAIL PROTECTED]> wrote:
> > reset :: (Prompt r -> r) -> r
> > shift :: Prompt r -> ((a -> _) -> r) -> a
>
> The point of the question is about shift/reset with *these types*. I
> know there are implementations with other type
On 2/22/08, Taral <[EMAIL PROTECTED]> wrote:
> reset :: (Prompt r -> r) -> r
> shift :: Prompt r -> ((a -> _) -> r) -> a
The point of the question is about shift/reset with *these types*. I
know there are implementations with other types.
--
Taral <[EMAIL PROTECTED]>
"Please let me know if the
Hello,
Found this:
http://www.theregister.co.uk/2007/08/21/sun_transactional_memory_rock/
http://research.sun.com/spotlight/2007/2007-08-13_transactional_memory.html
vasya
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskel
On Fri, Feb 22, 2008 at 10:57 AM, Reinier Lamers <[EMAIL PROTECTED]>
wrote:
> [...]
> Of course, the source code includes comments that specify what
> functions do, and so provide a bit of API documentation. But such
> comments should contain as little formatting as possible to keep them
> readabl
See also,
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/CC-delcont
"An implementation of multi-prompt delimited continuations based on the
paper, A Monadic Framework for Delimited Continuations, by R. Kent
Dybvig, Simon Peyton Jones and Amr Sabry"
reset :: MonadDelimitedCont
You might want to take a look at
http://www.haskell.org/pipermail/haskell/2007-December/020034.html
which shows an implementation of delimited continuations in Haskell98
and possibly gets rid of any requirement of implementing primitives.
-- ryan
On 2/22/08, Taral <[EMAIL PROTECTED]> wrote:
>
My understanding of these things is limited, but what would stop me,
theoretically speaking, of making a version of ghc with these
primitives added:
type Prompt r
reset :: (Prompt r -> r) -> r
shift :: Prompt r -> ((a -> _) -> r) -> a
(Where _ is either r or forall b. b)
--
Taral <[EMAIL PROTE
Actually, the second argument is already strict, and the ! doesn't make
it any stricter (and is therefore gratuitous): when you evaluate the
conditional (n == 0), n is evaluated.
Dan
Thomas Hartman wrote:
On second thought... never mind.
The only thing of (somewhat marginal) interest that my
On second thought... never mind.
The only thing of (somewhat marginal) interest that my latest comment
adds is that the second argument doesn't need to be strict.
Otherwise my code is exactly identical to Dan's.
2008/2/22, Thomas Hartman <[EMAIL PROTECTED]>:
> This was easier for me to understan
This was easier for me to understand when written so, with the start
value explicit
times3 :: (a -> a) -> Int -> (a -> a)
times3 f n !start | n == 0 = start
| otherwise = times3 f (n-1) (f start)
-- no stack overflow :)
tTimes3 = times3 (+1) 100 0
Here, only the
bit:
> I also have made haskell bindings to FreeType, including support for
> extracting glyph outlines.
>
> I haven't had time to publish it yet. Hopefully I'll get around to it
> soon.
Do you need a place to host the repository? code.haskell.org
is available if you want to host there.
Just vis
Op 22-feb-2008, om 1:54 heeft Conal Elliott het volgende geschreven:
The goal redesigning for composability is that we get more for
less. Haddock can focus on its speciality, namely hyperlinked
Haskell code documentation, and pandoc on its, namely human-
writable and -readable prose with mo
jefferson.r.heard:
> So the reason I keep pinging the list so much of late is I'm currently
> writing a GLUT program to visualize a heirarchical clustering of
> 18,000+ protein-protein interaction pairs (and associated
> gene-ontology terms). Thanks for the help on reading CSVs, those who
> wrote
Hi Yitzchak,
About "-- |", "-- ^", and "-- $doc", we might call them "markup
meta-directives", since they delimit the text to be preprocessed and then
produced as markup. The meta-directives and the "-- " line prefixes would
be removed in the process.
As for producing machine-readable API metada
Bulat Ziganshin gmail.com> writes:
>
> Hello haskell-cafe,
>
> is there any haskell implementation for Windows Mobile? does they are
> support creation of GUI apps and internet networking features?
>
Hugs is available for Windows CE, (I have it on my Jornada 720), but I've only
used it for n
Thanks. There seems to be some consensus developing around using
IORefs to hold all the program state.
-- Jeff
On Fri, Feb 22, 2008 at 12:11 PM, Brandon S. Allbery KF8NH
<[EMAIL PROTECTED]> wrote:
>
> On Feb 22, 2008, at 9:15 , Jefferson Heard wrote:
>
> > Now I'm to the point of making this t
On Feb 22, 2008, at 9:15 , Jefferson Heard wrote:
Now I'm to the point of making this thing interactive, and I I'm
trying to figure out the Haskell way of doing this. Last time I wrote
a program like this, I made a record data type with all the state and
placed it into an IORef and curried it
Kai wrote:
Wouldn't it be great if I had a visual tool that visually
showed me the graph while the above evaluation unfolded?
Does anybody know if such a tool exists?
I don't know of such a tool, the closest one to that is probably the new
ghci debugger.
There is also a paper and accompanyi
Hello dainichi,
Friday, February 22, 2008, 6:55:54 PM, you wrote:
> If nothing similar exists, I was thinking about creating such a
> tool (i.e. an interpreter with additional graph-displaying features)
not exactly this, but now i'm reading introduction into Q language [1]
which says on p.11 "Th
On Fri, Feb 22, 2008 at 2:42 PM, Daniel GorĂn <[EMAIL PROTECTED]> wrote:
>
> On Feb 21, 2008, at 7:55 PM, Roel van Dijk wrote:
>
> > Your solutions allows a bit more but fails with the equivalent of
> >
> > def foo():
> > for i in range(10):
> > if i == 6:
> > return None
> >
>
2008/2/22 <[EMAIL PROTECTED]>:
> Does anybody know if such a tool exists? I'd be grateful for pointers if it
> does. I very much doubt that I'm the first person who has thoughts like
> this, but then again, who knows. People who really know Haskell might think
> this is too trivial a task to reall
Thank you all. I am satisfied with all your inputs.
Tope
On Fri, Feb 22, 2008 at 7:17 AM, Christian Maeder <[EMAIL PROTECTED]>
wrote:
> TOPE KAREM wrote:
> > Thanks. My question is whether it can call a function (say map)
> > previously defined elsewhere in the program. Same goes for filter.
>
>
Hi Haskell-Cafe,
I'm relatively new to Haskell, but have a background with SML. One of the
things that amaze me about Haskell is lazy graph reduction, e.g. how the
graph unfolds during the evaluation of, say,
let fibs = 1 : 1 : zipWith (+) fibs (tail fibs) in take 10 fibs
Lazy lists can be simul
On 2/21/08 3:57 PM, Duncan Coutts wrote:
> Consequently there is no support in
> Cabal etc for those kinds of documentation. GHC, Cabal and c2hs amongst
> others use docbook but it's a horrible format to write and the tools to
> process it are very finicky (we apparently have to hard code paths to
TOPE KAREM wrote:
> Thanks. My question is whether it can call a function (say map)
> previously defined elsewhere in the program. Same goes for filter.
I'm still not sure what to answer. If map and filter were user defined
functions they may occur anywhere in your current module (or must be
impor
[cc-ed to hopengl list; are there many haskell opengl users
not on that list, btw?]
a standard package for easy-to-use, high-quality, portable
font support would make a great addition to haskell's
otherwise nice opengl bindings!
is there a reason for going directly to freetype? from the
old
I was trying to solve a similar problem while learning the FastCGI
package. The regular CGI package allows the use of ReaderT to hold
config data. Because FastCGI does the running of the passed in CGI
action within a few calls to alloca :: (Ptr a -> IO b) -> IO b, I
couldn't figure out a way to u
I also have made haskell bindings to FreeType, including support for
extracting glyph outlines.
I haven't had time to publish it yet. Hopefully I'll get around to it soon.
On Mon, Feb 18, 2008 at 5:07 AM, Jeremy Shaw <[EMAIL PROTECTED]> wrote:
> At Mon, 18 Feb 2008 01:26:17 +,
>
> Luke Palmer
Am Freitag, 22. Februar 2008 15:22 schrieb TOPE KAREM:
> Thanks. My question is whether it can call a function (say map) previously
> defined elsewhere in the program. Same goes for filter.
>
> Tope
Like
oddlyMakeEven [] = []
oddlyMakeEven ks@(k:_) = if odd k then map (*2) ks else filter even ks
Thanks. My question is whether it can call a function (say map) previously
defined elsewhere in the program. Same goes for filter.
Tope
On Fri, Feb 22, 2008 at 6:04 AM, Christian Maeder <[EMAIL PROTECTED]>
wrote:
> TOPE KAREM wrote:
> > I know the following:
> >
> > [1] That the general form of
So the reason I keep pinging the list so much of late is I'm currently
writing a GLUT program to visualize a heirarchical clustering of
18,000+ protein-protein interaction pairs (and associated
gene-ontology terms). Thanks for the help on reading CSVs, those who
wrote me back... my program intiti
TOPE KAREM wrote:
> I know the following:
>
> [1] That the general form of conditional expression is: if
> *Boolean_expression* then /exp1/ else /exp2
> /[2] That a conditional expression must always have both a then and an
> else expression.
> [3] That both /exp1/ and /exp2/ must have the same ty
I know the following:
[1] That the general form of conditional expression is: if *
Boolean_expression* then *exp1* else *exp2
*[2] That a conditional expression must always have both a then and an
elseexpression.
[3] That both *exp1* and *exp2* must have the same type, which is the type
of the ent
A quick note here. This is a *really* excellent tutorial on a variety
of subjects. It shows how monad operators can be used responsibly (to
clarify code, not obfuscate it), it shows how chosing a good data
structure and a good algorithm can work wonders for your code, and on
a simplistic
Conal Elliott wrote:
> Pare the Haddock markup language down to
> very few markup directives, say just 'foo' and
> "Foo.Bar".
Other critical ones:
-- | This shows which syntax this text describes.
-- ^ So does this.
Less critical, but usually not provided by general
markup languages:
-- $doc A
On Fri, Feb 22, 2008 at 9:31 AM, Thomas Schilling
<[EMAIL PROTECTED]> wrote:
> On 22 feb 2008, at 08.18, Jules Bean wrote:
> >
> > You can't call a stream-abstraction utility using a left-fold-
> > enumerator without cheating (unsafeInterleave), because the stream-
> > abstraction is incompati
On 22 feb 2008, at 08.18, Jules Bean wrote:
Thomas Schilling wrote:
On 21 feb 2008, at 18.35, Johan Tibell wrote:
I switched from lazy bytestrings to a left fold in my networking
code
after reading what Oleg wrote about streams vs folds. No problems
with
handles, etc. anymore.
Do you f
Felipe Lessa wrote:
On Thu, Feb 21, 2008 at 8:58 AM, Luke Andrew <[EMAIL PROTECTED]> wrote:
test2.hs:
import Control.Parallel
fib1 n = if n == 0 then 0 else if n == 1 then 1 else fib1 (n-1) +
fib1 (n-2)
fib2 n = if n == 0 then 0 else if n == 1 then 1 else fib2 (n-1) +
fib2 (n
46 matches
Mail list logo