Hi Christopher,
I made a small library to convert between strings and roman numerals [1].
It didn't use much abstraction. I mainly used some type-classes so multiple
string-like types can be parsed.
The numerals themselves are basically a concatenation of value symbols. The
order from high to low
Related to Karl's Template Haskell suggestion you could also have a look at
quasiquotation:
http://www.haskell.org/haskellwiki/Quasiquotation
The GHC documentation has an example of a expression quoter:
http://www.haskell.org/ghc/docs/latest/html/users_guide/template-haskell.html#th-quasiquotati
tch on the list of replacements to get both the
> -- entire list rs, the first element r and the tail rs'.
> loop rs@(r:rs') text =
> let (prefix, rest) = splitAt n text
> in if findStr == prefix
> then r ++ loop rs' rest
> else hea
I stared at the code some more and deduced what I think is the
intented meaning. Occurences of 'findStr' in 'myText' are replaced
with the strings in 'replaceStrList'.
So replaceBasedIdx "X" ["b","d","f"] "aXcXeXg" = "abcdefg"
The reason your counter didn't increment is because it was defined as
Hi John,
Can you tell us what your function is supposed to do? It appears to be some
kind of search-and-replace for strings. What is the relationship between
'findStr', 'replaceStrList' and 'myText'?
2013/5/8 John
> Hello All,
>
> I'm in a big trouble with incrementation of a counter in this c
For each package "myPackage" Cabal generates a module containing,
among other things, the package's version as a Haskell value:
> import Paths_myPackage ( version )
> import Data.Version ( showVersion )
> main = showVersion version
See also "Accessing data files from package code" in
http://www.
Hello,
I have a program which I believe can benefit from concurrency. But I
am wondering if the mechanisms I need already exist somewhere on
Hackage.
Here is a sketch of my program, in literate Haskell:
> module Problem where
> import Control.Monad ( forM_ )
The producer produces values. It blo
bzlib-0.5.0.2 suffers from the exact same problem. I send a bug report
to the author a few days ago, but I can imagine he's very busy. It
might help if we can send patches that fix the compile error.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
Have you tried using putStrLn?
Small GHCI example:
Prelude> putStrLn "\29579"
王
I believe the Show instances for chars and strings escape all
characters with a codepoint > 127.
2012/1/10 Magicloud Magiclouds :
> Hi,
> I am using LDAP hackage to do some ldap searching. I am not sure if
> th
2011/10/18 Roel van Dijk :
> Maybe we [can] create an example program which would fail with the
> more general type.
Migrating the function "foo" from bytestring to vector-bytestring
would fail with more general types:
> import Data.ByteString
> foo = print empty
Ok, modul
2011/10/18 Christian Maeder :
> you could re-export VS.empty, VS.singleton, etc. directly.
The vector singleton and the vector-bytestring singleton don't have
the same type.
vector:
> singleton :: a -> Vector a
vector-bytestring:
> singleton :: Word8 -> Vector Word8
By choosing the more general
{- forgot to reply to list -}
This isn't Haskell syntax. Atleast not directly. It is either
hsc2hs[1] or c2hs [2]. Also see [3] for the difference between the
two. Soin order to compile that code you first have to run it through
aspecial preprocessor.
1 - http://www.haskell.org/ghc/docs/7.2.1/html
Unfortunately the bifunctor.homelinux.net domain stopped working. The
reverse dependencies can now be found at:
http://revdeps.hackage.haskell.org/
The reverse dependency algorithm needs some love. Some packages have
-1 reverse dependencies, which is somewhat strange.
___
I see the aeson version with the stricter dependency on deepseq < 1.2
is now also released on hackage:
http://hackage.haskell.org/package/aeson-0.3.2.12
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haske
I believe this is because of aeson depending on *any* version of
deepseq. This was very recently fixed in the development version:
https://github.com/mailrank/aeson/pull/25
2011/9/20 Rune Harder Bak :
> Sometimes when one of our developers (using Arch-linux) tries to cabal
> install packages he
> Are you familiar with the Grammatical Framework [1]? It is a Haskell
> library and language for natural language parsing and translation --
> If you need to do a lot of translation or string localization, you
> should take a look at it as much of the complexity has been addressed
> there.
Yes. S
0
cardinal numbers. But after that information is sparse. You can help
by checking and expanding the test suite. This is very simple because
the test suite consists only of numbers combined with the expected
cardinal number word.
Regards,
Roel van Dijk
___
Hask
2011/9/12 Brandon Allbery :
> Don't all infix constructors have to start with a colon?
Yes that is true. You can of course use Unicode symbols as infix type variables:
(⋙) :: Category ⇝ => (α ⇝ β) -> (β ⇝ γ) -> α ⇝ γ
But a constructor must always begin with a capital letter or with a colon.
Uni
Does it help if you format it like this:
-- |Apply a given function over all elements of a list and select one of the
-- results.
selector :: (Arbitrary b)
=> [a] -- ^ Elements to select from
-> (a -> b) -- ^ Constructor to apply to selected element
-> Gen b
selec
On 20 May 2011 12:46, Markus Läll wrote:
> What's stopping it from being put on the official hackage? I use it quite a
> lot to find well established packages and/or example code, and am quite fond
> of it. But it is only visible when you know that this exists.
Poor timing. I wrote the patch when
On 19 May 2011 20:50, Serguey Zefirov wrote:
> The solution... I think that some ratings, like "used directly by ###
> packages/projects and indirectly by ###" would be nice, but not much.
Maybe my reverse dependencies mirror of hackage could be useful here:
http://bifunctor.homelinux.net/~roel/h
On 10 May 2011 09:47, Andrew Butterfield wrote:
> Why not indeed ?
> (-->) = flip (.)
> f = Main.id --> show --> (++ " = message received") --> putStrLn
-- (>>>) :: Category cat => cat a b -> cat b c -> cat a c
import Control.Category ( (>>>) )
f = Main.id >>> show >>> (++ " - message received")
On 24 April 2011 01:49, wren ng thornton wrote:
> I would *love* there to be a tool which (a) automatically saves failing
> QuickCheck values to disk, and (b) automates using HUnit to load those in
> and test them. I'm not so sure that QuickCheck should be doing the second
> step of that since tha
On 13 April 2011 21:26, Tim Chevalier wrote:
> IO doesn't obey the monad laws, due to the presence of seq in Haskell.
> Sad but true...
See also a previous discussion about IO and the Monad laws:
http://www.haskell.org/pipermail/haskell-cafe/2010-March/074001.html
__
On 5 April 2011 07:04, Mark Lentczner wrote:
> I'm not on that mailing list, so I'll comment here:
I recommend joining the prime list. It is very low traffic and the
place where language changes should be discussed.
> My only caveat is that the encoding provision should apply when Haskell
> sour
I made an official proposal on the haskell-prime list:
http://www.haskell.org/pipermail/haskell-prime/2011-April/003368.html
Let's have further discussion there.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/list
2011/4/4 Ketil Malde :
> I think the safest thing to do is to require source to be ASCII, and
> provide escapes for code points >127...
I do not think that that is the safest option. The safest is just
writing down whatever GHC does. Escape codes for non-ASCII would break
a lot of packages and mak
On 4 April 2011 12:22, Michael Snoyman wrote:
> Firstly, I personally would love to insist on using UTF-8 and be done with
> it. I see no reason to bother with other character encodings.
This is also my preferred choice.
> There *is* an algorithm for determining the encoding of an XML file based
2011/4/4 Colin Adams :
> Not from looking with your eyes perhaps. Does that matter? Your text editor,
> and the compiler, can surely figure it out for themselves.
I am not aware of any algorithm that can reliably infer the character
encoding used by just looking at the raw data. Why would people bo
Hello,
The Haskell 2010 language specification states that "Haskell uses
the Unicode character set" [1]. I interpret this as saying that,
at the lowest level, a Haskell program is a sequence of Unicode
code points. The standard doesn't say how such a sequence should
be encoded. You can argue that
Nice work!
The view file part seems to have problems with utf-8 encoded files:
http://handra.rampa.sk/dawb/view?repoVURL=http%3A%2F%2Fcode.haskell.org%2Fnumerals&repoVFile=test%2FText%2FNumeral%2FLanguage%2FZH%2FTestData.hs
It is unreadable even when explicitly asking my browser to decode the
doc
I can reproduce the problem on my system with GHC-7.0.3.
The flag old-base is meant for base libraries before 3.0.3.1 which
didn't export a Control.Category module. It looks like I accidentally
inverted the logic of the flag. What is weird is that is still builds
okay on my system. I would expect
Remember that constructors are functions, except that you can't
pattern match against them.
> data MyType = GeneralConstructor [Double]
> -- GeneralConstructor :: [Double] -> MyType
Note the lower case character, just a plain function:
> specialConstructor :: Double -> MyType
> specialConstructo
I checked out the GHC documentation on the GADTs extension [1]:
"The key point about GADTs is that pattern matching causes type
refinement."
So in
tr2 (Tree Int) (Node _ (t:_)) = Node 1 [t]
the 'a' in 'Type a' is refined to 'Type (Tree a)'.
But in
tr1 (Node _ (t:_)) (Tree Int) = Node 1 [t]
y
I believe this is caused by type equalities that are introduced by the
Type a argument. In tr2 you get something like a ~ Int or a ~ String,
allowing the function to type check. In tr1 that equality is never
introduced so the type checker thinks a and Int are distinct types.
But I'm sure someone e
Both your replies where very helpful. I combined both approaches to
get nearer to what I want.
> class Lit α where lit ∷ Integer → α
> class Add α where add ∷ α → α → α
> instance Lit Integer where lit = fromInteger
> instance Add Integer where add = (+)
This time I require TypeSynonymInstances:
Hello everyone,
I am stuck rewriting some code in the tagless style. My problem can be
thought of as an interpreter for a very simple language:
> data Exp = Lit Integer
> | Add Exp Exp
> | Mul Exp Exp
>deriving (Show)
But some complexity is added by the fact that my
In general code compiled with GHC will be a lot faster than code
interpreted by GHCI. You can also call compiled code from within GHCI,
in which case you would hardly see a performance difference.
On 22 February 2011 08:26, C K Kashyap wrote:
> Hi,
> Is there a runtime performance difference betw
I believe code.haskell.org has moved to a new machine. Its IP address
also changed, which causes your ssh to issue a warning. You can fix it
by deleting the code.haskell.org entry from your local
~/.ssh/known_hosts file.
On 16 February 2011 18:58, Henning Thielemann
wrote:
>
> Thank you a lot for
On 7 February 2011 22:00, Andrew Coppin wrote:
> I clearly have my languages mixed up.
>
> The language I'm thinking of required all variables (even top-level ones) to
> be declared with "let" - unless the definition is recursive, in which case
> you have to say "letrec" (i.e., the compiler it too
On 5 February 2011 16:21, Andrew Coppin wrote:
> I didn't think Clean supported laziness at all? I thought it was a strict
> language.
"CLEAN is a practical applicable general-purpose lazy pure functional
programming language suited for the development
of real world applications." [1]
Haskell en
Thank you for your reply. I will follow progress on the ticket.
On Mon, Nov 8, 2010 at 3:57 AM, Vivian McPhail
wrote:
> Here's the ticket:
>
> http://hackage.haskell.org/trac/ghc/ticket/781
>
> They aim to fix the problem (with fPIC) by ghc 7.2.
>
> Cheers,
>
> Vivian
Cool, this means hmatrix is still an option for my fitting problem.
The problem is a bit annoying but I can work with it.
My assumption about the cause of the problem (wrong number of
arguments) made me miss the real problem.
Thanks for the explanation.
___
Hello,
I would like to use hmatrix to do some function fitting with the
Levenberg Marquardt algorithm. As an example I would like to fit the
very simple function "f x = a*x + b" on some data points. The problem
is that executing the 'fitModel' function crashes GHC(i) with a
segmentation fault. Thi
Yes, that would prevent the shadowing. But now you are ignoring the
argument op1. Choosing a name that is more different from 'op' might
be helpful. You can even invent your own operator as an argument to
your commutative function:
commutative (⊕) = \a b -> (a ⊕ b) == (b ⊕ a)
On Mon, Nov 1, 201
> I think somebody else already mentioned region-based management, which is
> also completely safe AFAIK.
Ben Franksen mentioned my brother's regions package [1]. He's about to
release a new version with simpler type machinery. The list of
packages that make use of the regions package [2] can serv
The darcs installed on code.haskell.org is still version 2.02. It
doesn't know about 'optimize --upgrade'. How do I upgrade those
repositories?
On Sat, Oct 9, 2010 at 2:30 PM, Christopher Done
wrote:
> Every Darcs repository I've pulled this year has always showed me this
> message:
>
>
I really like the lambda-case. There are dozens of places in my code
where I could use it.
Not so sure about the lambda-if. It is just as easily done using an
ordinary function.
lambda-case: +1
lambda-if: neutral
___
Haskell-Cafe mailing list
Haskell-Ca
Here is a list of fonts that support that particular character:
http://www.fileformat.info/info/unicode/char/2237/fontsupport.htm
I think I'll add a little font overview to my unicode-symbols wiki
page. Most Unicode symbols that are useful in Haskell are not terribly
obscure and supported by a wid
I align my imports by hand, but your Emacs scripts look useful. I
think I'm going to use them too.
Another extremely useful function for aligning is align-regexp.
On the subject of coding style, I can work with almost any style as
long as it is used somewhat consistently. Personally I try to opti
Impressive! I didn't think you could implement it so quickly.
Now someone needs to add this functionality to Leksah or hack
something up for Emacs.
Regards,
Roel
On Sun, Sep 19, 2010 at 8:27 PM, Paul Brauner wrote:
> It works:
>
> brau...@worf:/tmp$ cat test.hs
> import Test.QuickCheck
> import
In my haste to reply I made an error in my 'newby' multiplication
function. Pesky negative numbers...
intMul ∷ Integer → Integer → Integer
intMul x n | n < 0 = -(intMul x $ abs n)
| n == 0 = 0
| n > 0 = x + intMul x (n - 1)
I do wonder what happens when haltavista
Very interesting!
It got me thinking: if you combine this with the Arbitrary class [1]
of QuickCheck you can use it check if you have defined a function that
is "equal" to an already defined function.
Let's say I write the following function:
intMul ∷ Integer → Integer → Integer
intMul x 0 =
On Mon, Aug 23, 2010 at 8:07 AM, Richard O'Keefe wrote:
> But what _is_ "the core functionality".
> The Single Unix Specification can be browsed on-line.
> There is no part of it labelled "core"; it's all required
> or it isn't AWK. There are weird little gotchas like
> File "foo" = '{ pri
On Tue, Aug 17, 2010 at 3:53 AM, Richard O'Keefe wrote:
> On Aug 17, 2010, at 12:37 AM, Roel van Dijk wrote:
>>
>> phi = (1 + sqrt 5) / 2
>> fib n = ((phi ** n) - (1 - phi) ** n) / sqrt 5
>>
>> The use of (**) should make the complexity at least O(n). Please
On Sat, Aug 14, 2010 at 5:41 PM, Andrew Coppin
wrote:
> (Then again, the Fibonacci numbers can be computed
> in O(1) time, and nobody ever needs Fibonacci numbers in the first place, so
> this is obviously example code.)
A bit off-topic, but I don't think there exists a function that
computes fi
Have you read Wouter Swierstra's "Data Types A La Carte" [1]?
Whether it uses basic and easy parts of Haskell depends on your
mindset. You need to wrap your head around the fixpoint. It requires
at least the MultiParamTypeClasses language extension.
Regards,
Roel
1 - http://www.cs.nott.ac.uk/~ws
Note the following line from the haskell-mode project page: "If it
works on XEmacs, consider yourself lucky." [1]
Regards,
Roel
1 - http://projects.haskell.org/haskellmode-emacs/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.
Google translation:
> The office of our company is located in Nice - the heart of the
> Riviera, that gives us an immediate opportunity to offer villas
> for rent and sale in all their diversity, as well as guidance to
> our clients on the most interesting and important events in the
> rich cultura
Use our threads package [1].
import Control.Concurrent.Thread ( forkIO, wait_ )
myDBusThingie :: IO ()
myDBusThingie = error "TODO"
main :: IO ()
main = do tid <- forkIO myDBusThingie
wait_ tid
But like David said, this is only usefull if you plan on multiple
concurrent waits or doin
On Thu, May 13, 2010 at 5:23 PM, Stephen Tetley
wrote:
> Hi Bas
>
> I'm not entirely surprised...
>
> Do you know if haskell-src-exts can parse files with Unicode syntax
> (and I'm not using enough extensions)?
>
> Thanks
>
> Stephen
Last time I checked it had problems with the ∷ and ∀ characters
>From the Haskell 98 report (section 6.3.4):
> For Float and Double, the semantics of the enumFrom family is given by the
> rules for Int above, except that the list terminates when the elements become
> greater than e3+i/2 for positive increment i, or > when they become less
> than e3+i/2 f
I think it would be nice in general to be able to mirror at least
hackage.haskell.org. Something like rsync would be close to ideal for
this purpose.
Reasons I would like to mirror hackage:
1 - Provide alternative when the main hackage is down
2 - Access to the sources of all uploaded packages for
Here is my attempt. I tried to avoid higher concepts like folds and
things like the ($) operator. Most recursions are written explicitly.
{ BEGIN CODE }
module Main where
-- Data type representing a door which is either Open or Closed.
data Door = Open | Closed deriving Show
toggle :: D
In my opinion code is 'right' when it conforms to the specification.
Haskell's type system allows the programmer to express a part of the
specification in the types, which then get checked by the
compiler/type-checker. This is where I see the biggest benefit of a
very expressive statically checked
The problem could be in your use of forkIO.
To quote the documentation of forkOS [1]:
>Like forkIO, this sparks off a new thread to run the IO computation passed as
>the first argument, and returns the ThreadId of the newly created thread.
>However, forkOS creates a bound thread, which is necess
On Wed, Apr 14, 2010 at 2:32 AM, Ivan Miljenovic
wrote:
> Why not use Maybe for func1 in the first place? Or are you wanting to
> automagically make all uses of head, tail, etc. safe?
In which case there is already the 'safe' package:
http://hackage.haskell.org/package/safe
_
Can anyone provide an example of an error that is prevented by this
warning? When exactly is it dangerous to ignore a monadic function's
return value?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-c
On Tue, Apr 6, 2010 at 1:08 PM, Serguey Zefirov wrote:
> http://lambda-the-ultimate.org is one lovely community that has that
> restriction: http://lambda-the-ultimate.org/policies#Policies
LtU has no restriction on user names. From LtU's policy:
> Anonymity and the use of pseudonyms is discourag
Programming in Haskell certainly makes me feel gay.
define gay
cheery: bright and pleasant; promoting a feeling of cheer; "a cheery
hello"; "a gay sunny room"; "a sunny smile"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/
I tried a few things. First I added another timeout to main, so the
program kills itself after a few seconds.
doit :: IO (Maybe ())
doit = timeout 1200 $ {- yield >> -} return ()
main :: IO ()
main = do _ <- timeout 500 $ forever doit
return ()
This program failed to terminate.
The documentation for Data.Version might be insightful:
http://haskell.org/ghc/docs/latest/html/libraries/base-4.2.0.0/Data-Version.html
If Cabal uses the parseVersion function to parse versions then the
following version is valid: "1.2.3-a-b-c". If should result in this
value:
Version {versionB
I think these reddit posts are relevant:
First announcement:
http://www.reddit.com/r/haskell/comments/b58rk/try_haskell/
Second announcement:
http://www.reddit.com/r/haskell/comments/b7dil/try_haskell_now_with_t_and_wip_interactive/
___
Haskell-Cafe mai
What I usually do in such a case is create a separate internal
module. The internal module exports everything. Then create a
module which defines the public interface. This module simple
reexports symbols from the internal module. Now you can create a
Test module which has full access to all intern
Hello,
We would like to announce an update of concurrent-extra [1].
Bug fixes:
- A bug in RLock.acquire (thanks to Felipe Lessa).
New features:
- Broadcast: Wake multiple threads by broadcasting a value. This
is a generalisation of Event.
- Thread: Threads extended with the ability to wai
On Wed, Feb 17, 2010 at 3:27 PM, Felipe Lessa wrote:
> In acquire (l. 111), if the lock was already acquired it goes by
>
> | otherwise → do putMVar mv mb
> Lock.acquire lock
>
> So it puts back the information about the owner of the RLock and
> waits for its rel
Hello,
We would like to announce the release of concurrent-extra [1]. A
library which offers a few extra synchronization primitives. These
primitives are found in the standard libraries of languages like Java
and Python, but not in Haskell.
Quick overview:
* Lock: Enforce exclusive access to a r
2010/2/17 Neil Brown :
> You don't need to do use ThreadId: MVar has an Eq instance, so you could
> make your Lock type derive an Eq instance, and then you can just compare the
> Locks to remove it after the timeout occurs (e.g. using delete to take it
> out of the list; it should be quite near the
2010/2/16 Simon Marlow :
> You might want to take a look at the concurrency part of the GHC test suite:
>
> http://darcs.haskell.org/testsuite/tests/ghc-regress/concurrent/should_run/
>
> Not that we've really solved the problem you're talking about, but you might
> get some ideas.
The method of t
2010/2/16 Neil Brown :
> I had a look at the code for Event (both versions) and Lock (but not the
> others just yet) and it seemed fine. If you do lots of calls to waitTimeout
> before a set you will accumulate old locks in the list, but that won't cause
> any error that I can see, so it would onl
Hello,
We wrote a small library (1) which offers a few extra synchronization
primitives. These primitives are found in the standard libraries of
languages like Java and Python, but not in Haskell.
Before releasing concurrent-extra on hackage, we would like some
comments on its name, design, imple
s get http://code.haskell.org/~roelvandijk/code/ftdi
Regards,
Roel van Dijk
1 - http://hackage.haskell.org/package/ftdi
2 - http://ftdichip.com/
3 - http://hackage.haskell.org/package/usb
4 - http://www.intra2net.com/en/developer/libftdi/
5 - http://www.ftdichip.com/Driver
On Thu, Jan 21, 2010 at 3:06 PM, Daniel Fischer
wrote:
> But I find it easier to let Cabal deal with haddock, make a Cabal package,
>
> runghc ./Setup.hs configure --user --prefix=$HOME
> runghc ./Setup.hs haddock --hyperlink-source
If you use a Cabal package in conjunction with cabal-install it
On Wed, Jan 20, 2010 at 12:57 PM, Sean Leather wrote:
> I did some conditional Haddocking in EMGM. See, for example:
> http://hackage.haskell.org/packages/archive/emgm/0.3.1/doc/html/src/Generics-EMGM-Data-Bool.html
At first I didn't see what you did differently. Until I checked your
Setup.lhs. I
> Doesn't haddock define __HADDOCK__ by itself?
That appears to be a common misconception. The discussion on this
ticket [1] indicates that haddock does *not* define __HADDOCK__. So I
can not rely on it being defined. Therefore I would like to define it
myself, but only in the case that haddock is
abal used to define the __HADDOCK__ macro. Is it possible to
manually define a preprocessor macro when haddock is run? Perhaps an
equivalent to ghc-options: haddock-options?
Ideally I want only have to add the following to my .cabal file:
> haddock-options: -D__DOC__
Regards
On Sun, Jan 17, 2010 at 12:27 PM, Ketil Malde wrote:
> I think there might be justification for doing it multiple places. The
> cabal file tells you what is required to build the package, the pragmas
> what is required to build each source file.
>
> Perhaps cabal should complain when source files
> It's in the process of moving to a new (and hopefully more reliable) host.
That is good news. Nice work!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
I wrote a small cronjob to update my hackage reverse-deps. When
checking if it worked I noticed that my hackage appears to be more
up-to-date than the real thing!
Compare the "What's new" of both:
Real hackage: http://hackage.haskell.org/packages/archive/recent.html
Play thing:
http://bifunctor.
On Thu, Jan 14, 2010 at 12:47 PM, Colin Paul Adams
wrote:
>>>>>> "Roel" == Roel van Dijk writes:
>
> Roel> I think it is time for an Obfuscated Haskell Contest :-)
>
> Are you allowed to use obsolete scripts for your identifiers? :-)
Sure, I'll
> Thus speaketh the report (http://haskell.org/onlinereport/lexemes.html):
>
> symbol -> ascSymbol | uniSymbol
> ascSymbol -> ! | # | $ | % | & | * | + | . | / | < | = | > | ? | @
> | \ | ^ | | | - | ~
> uniSymbol -> any Unicode symbol or punctuation
>
> P
2010/1/14 Evan Laforge :
> Wow, that's kind of cute:
>
> {-# LANGUAGE UnicodeSyntax #-}
> (*) = (*)
> (/) = (/)
> 公式 高 中 低 = 高 * 中 * 低 / 整數
> 整數 = 123
That code snippet is also perfectly legal Haskell without the
UnicodeSyntax language extension. You use UnicodeSyntax if you want to
write code lik
I have downloaded the torrent with the hackage archive from 19 oktober
2009 and put it on my server. This means you can now download all the
packages contained in that archive (only the latest versions at that
date).
Happy hacking,
Roel
On Wed, Jan 6, 2010 at 11:57 AM, Roel van Dijk wrote:
>
If you are desperate for some hackage you can at least browse packages
on my reverse dependencies thingie:
http://bifunctor.homelinux.net/~roel/hackage/packages/hackage.html
The last update was the 4th of january. But it doesn't have the actual
packages, so it is probably not so useful in this ca
I can't offer much insight but could the answer lie in the Integer
type? I suspect that with a sufficiently large fixed Int type (2^14
bits?) the performance of the two functions would be almost equal.
Could it be that the second function delays the multiplication of
large numbers as long as possi
2009/12/10 Richard O'Keefe :
> On Dec 10, 2009, at 2:58 AM, Roel van Dijk wrote:
>> I tried to be conservative with the choice of unicode symbols. I have
>> defined the division sign (÷) to be (/). But it could just as well be
>> defined as 'div'.
>
> No i
On Wed, Dec 9, 2009 at 4:20 PM, stefan kersten wrote:
> looks great, thanks! do you happen to have some example code for working with
> HID devices (mice, keyboards, etc.)?
The usb package does not support the various device classes directly.
You won't find a function like "isKeyPressed ∷ Device
s more symmetrical with (<) and (≤).
This package was inspired by unicode-prelude from Péter Diviánszky:
http://hackage.haskell.org/package/unicode-prelude
Regards,
Roel van Dijk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
things. All in wonderful
colours of course.
The only major change is that it now depends on usb-0.3.*
Regards,
Roel van Dijk
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Mon, Dec 7, 2009 at 10:24 AM, Lyndon Maydwell wrote:
> I had heard that Hoogle actually compiled any type-signatures, where
> as Hayoo just did a text comparison.
>
> I'm not actually sure if this is true or not though.
>
> If it is, it would mean that "[q] -> [r] -> [(q,r)]" would return zip
>
1 - 100 of 171 matches
Mail list logo