Am 29.09.2010 05:35, schrieb Peter Schmitz:
[...]
> Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1):
> unexpected end of input
> expecting "<"
>
> The input was:
[...]
>
>> -- Parsers:
>> taggedContent = do
>>optionalWhiteSpace
>>aTag
>>many tagOrContent
>>aTa
Don Stewart:
> tomahawkins:
> > A few years ago I attempted to build a Haskell hardware compiler
> > (Haskell -> Verilog) based on the Yhc frontent. At the time I was
> > trying to overcome several problems [1] with implementing a hardware
> > description language as a light eDSL, which convinced
Hi Tom,
You wrote that you are interested in the programming experience with relaxed
atomicity. What you are asking for are the ideas behind Twilight STM, written
in these papers:
> http://proglang.informatik.uni-freiburg.de/projects/syncstm/techreport2010twilight.pdf
(brief summary of the unde
On 28 sep 2010, at 17:33, Ozgur Akgun wrote:
> How do you define relationships between data types?
>
> Well, why is it any different from other fields? From one of your examples
> [1], I'd expect you to have a list of questions in the Quiz data type, and if
> necessary, a quiz field in the Ques
If you are really interested in embedded realtime code you may want to have a
look at the timber language[1] or bit-c[2]. Another very interesting project
is this[3] developing a new Haskell like language called Habit for systems
programming.
There are also some great papers about systems program
Am 29.09.2010 09:54, schrieb Christian Maeder:
> Am 29.09.2010 05:35, schrieb Peter Schmitz:
> [...]
>> Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1):
>> unexpected end of input
>> expecting "<"
>>
>> The input was:
> [...]
>>
>>> -- Parsers:
>>> taggedContent = do
>>>opt
OK, I am rephrasing it a bit then :)
I definitely don't think this would be trivial to implement. However, I'd
expect a decent solution to this problem, not to have special combinators to
describe relations between data types, but let the user model their data
using plain haskell data types, and in
I think this approach is not possible without involving some fairly
ugly unsafeInterleaveIO/unsafePerformIO calls. A simple example using
a common web programming example: support I have a multi-user blog
site, where each user can have multiple entries. I would model this
using standard Haskell dat
Ryan Ingram wrote:
I saw the winner was announced. Is there a highscore table? We were
in the top 5, I want to see how well we did.
Only the winners were announced at the conference - no highscore
table. The organisers may put more detail on the contest website
perhaps?
Regards,
M
Am 29.09.2010 11:55, schrieb Christian Maeder:
> Am 29.09.2010 09:54, schrieb Christian Maeder:
>> Am 29.09.2010 05:35, schrieb Peter Schmitz:
>> [...]
>>> Error parsing file: "...\sampleTaggedContent.txt" (line 4, column 1):
>>> unexpected end of input
>>> expecting "<"
>>>
>>> The input was:
>> [
On 28 September 2010 21:12, Jeremy Shaw wrote:
> Not sure what that means. But I am only willing to maintain so many
> wiki pages. So far at least three have come up in this thread.
Why?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.
lhae[1] is a spreadsheet program. It features a simple formula language
and some basic statistical methods, like descriptive statistics and pivot
tables.
0.0.2 -> 0.0.3:
---
Improvements:
- Right click menu at columns/row headers and cells
- Insert rows/columns between exisiting ro
A new graphics library:
http://hackage.haskell.org/package/collada-output
Most of the graphics libraries on hackage use OpenGL to visualize 3d
objects.
With this library you now have the choice to use an external tool for
visualization and enjoy the flexibility of
a standard format for 3d dat
I still cannot seem to get a GUI working under Windows.
For Haskell GUI's is Ubuntu easier to setup.
If so, we're losing people if Haskell GUI's are so hard to get working
under Windows.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http:
I have a question about Parsec. The following program
> import Control.Applicative ((*>),(<*))
> import Text.Parsec
> import Text.Parsec.Char
> block p = char '{' *> p <* char '}'
> parser = block (many digit)
> main = parseTest parser "{123a}"
gives the output
parse error at (line 1, column 5
I need the trick to get from
ByteString -> [GHC.Word.Word8]
and Hayoo is not helping.
Super simple I expected. I haven't even tried to compile it yet.
I am just trying to read in the bytes and encode with base64:
import Codec.Binary.Base64
import Data.ByteString
import System.Director
On Wed, Sep 29, 2010 at 11:03 AM, Roderick Ford wrote:
> I need the trick to get from
> ByteString -> [GHC.Word.Word8]
> and Hayoo is not helping.
>
> Super simple I expected. I haven't even tried to compile it yet.
> I am just trying to read in the bytes and encode with base64:
>
> import Codec.
By and large hayoo is the alta-vista of Haskell search - it has a huge
database but isn't well organized or good at prioritizing. Use Hoogle
when doing type-based searches for functions in the typical GHC load.
http://haskell.org/hoogle/?hoogle=%3A%3A+ByteString+-%3E+[Word8]
Also, what's with th
The idea was to go from
Prelude> :t Data.ByteString.readFile
Data.ByteString.readFile
:: FilePath -> IO Data.ByteString.Internal.ByteString
to here
Prelude> :t Codec.Binary.Base64.encode
Codec.Binary.Base64.encode :: [GHC.Word.Word8] -> String
unless there is another/easier way
R
In addition to hoogle I suggest you check out hackage too. I think
you'll be particularly interested in "base64-bytestring":
http://hackage.haskell.org/package/base64-bytestring
Cheers,
Thomas
On Wed, Sep 29, 2010 at 9:41 AM, Roderick Ford wrote:
> The idea was to go from
> Prelude> :t Data.By
YES!! Thank you so much.
And thanks to Thomas also for the suggestion of using Data.ByteString.Base64
... as the alternative method.
Cheers,
Roderick
> Date: Wed, 29 Sep 2010 11:11:01 -0500
> Subject: Re: [Haskell-cafe] can't find in hayoo
> From: aslat...@gmail.com
> To: develo...@live
Ben Franksen wrote:
>> import Control.Applicative ((*>),(<*))
>> import Text.Parsec
>> import Text.Parsec.Char
>> block p = char '{' *> p <* char '}'
>> parser = block (many digit)
>> main = parseTest parser "{123a}"
>
> gives the output
>
> parse error at (line 1, column 5):
> unexpected "a"
Hi,
on planet.debian.org, there is some ill-tempered discussion about the
seemingly bad relationship between the Ruby community and Debian
maintainers. The following blog post summarizes the issues quite well
and calmly:
http://gwolf.org/blog/ruby-dissonance-debian-again
With the Haskell communit
On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote:
> >
> > Note the last line mentions only '}'. I would rather like to see
> >
> > expecting "}" or digit
> >
> > since the parser could very well accept another digit here.
parsec2 did that, I don't know whether that change is intention
There are issues, yes, and you may need the MinGW tool chain to get the GUI
packages to build and install properly, but it does work. I have blogged
about some of my experiences, both good and bad, at
http://jpmoresmau.blogspot.com/. What GUI tool specifically do you want to
use?
JP
On Wed, Sep 2
On 29 September 2010 17:01, wrote:
> I still cannot seem to get a GUI working under Windows.
>
> For Haskell GUI's is Ubuntu easier to setup.
>
> If so, we're losing people if Haskell GUI's are so hard to get working under
> Windows.
We're losing people! Charge!
I think the problem is lack of W
Hi,
I have the following code:
{-# LANGUAGE TypeSynonymInstances #-}
data Vect k b = V [(k,b)]
-- vector space over field k with basis b
-- for example, V [(5, E 1), (7, E 2)] would represent the vector 5 e1 + 7 e2
data Monomial v = M [(v,Int)]
-- monomials over variables v
-- for example, M [(
Maybe -XLiberalTypeSynonyms is an option:
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/data-type-extensions.html#type-synonyms
On 29 September 2010 20:08, DavidA wrote:
> Hi,
>
> I have the following code:
>
> {-# LANGUAGE TypeSynonymInstances #-}
>
> data Vect k b = V [(k,b)]
> -- vec
On Wed, 29 Sep 2010 20:08:07 +0200, you wrote:
>I think the problem is lack of Windows developers interested in GUIs,
>and that Windows is not so POSIXy-development-friendly as Linux or OS
>X. But mostly lack of people interested in that area, I think.
There are lots of Windows developers "intere
I imagine that getting Haskell GUI libraries set and playing nice with
the native GTK libs is a pain on Windows.
That said, I know that Haskell has very nice Lua bindings and Lua has
pretty mature GTK bindings. Has anyone tried developing their UI in
Lua with Haskell doing all the heavy lifting?
On 29 September 2010 20:33, Steve Schafer wrote:
> There are lots of Windows developers "interested" in GUIs. [..]
> The issue isn't that there aren't a lot of Windows developers who have
> an interest in Haskell+GUI development.
Yeah, what do you think I meant? We're talking about the state of
On Wed, Sep 29, 2010 at 11:08 AM, DavidA wrote:
> Hi,
>
> I have the following code:
>
> {-# LANGUAGE TypeSynonymInstances #-}
>
> data Vect k b = V [(k,b)]
> -- vector space over field k with basis b
> -- for example, V [(5, E 1), (7, E 2)] would represent the vector 5 e1 + 7 e2
>
> data Monomial
On 29 September 2010 20:48, Ryan Ingram wrote:
> But it doesn't let you partially apply the type synonym.
>
> On the other hand, if you did this:
>
> newtype Compose f g a = O { unO :: f (g a) }
> type Poly k = Compose (Vect k) Monomial
>
> instance Monad (Poly k) where ...
>
> would work, but now
On Wednesday 29 September 2010 2:52:21 pm Christopher Done wrote:
> LiberalTypeSynonyms lets you partially apply type synonyms.
Not in general. LiberalTypeSynonyms only allows synonyms to be partially
applied when expansions of other type synonyms will eventually cause them to
become fully appli
On Wed, 29 Sep 2010 20:44:22 +0200, you wrote:
>Yeah, but not liking wrestling with libraries isn't peculiar to
>Haskell developers. There just needs to be enough people that the
>probability of there being a person who will bother to wrestle with it
>is high enough. Hence, the issue is lack of in
S. Doaitse Swierstra schrieb:
> Avoiding repeated additions:
>
> movingAverage :: Int -> [Float] -> [Float]
> movingAverage n l = runSums (sum . take n $l) l (drop n l)
> where n' = fromIntegral n
>runSums sum (h:hs) (t:ts) = sum / n' : runSums (sum-h+t) hs ts
>run
On 29/09/2010 02:18 PM, Henning Thielemann wrote:
Andrew Coppin wrote:
Tastes do indeed vary. To me, both of these are incorrect, and the
correct way is
data Foo a b =
Fooa |
Bar b |
Foobar a b
deriving (Eq, Ord)
The truth is: Given the separator style of
Daniel Fischer wrote:
> On Wednesday 29 September 2010 19:10:22, Ben Franksen wrote:
>> >
>> > Note the last line mentions only '}'. I would rather like to see
>> >
>> > expecting "}" or digit
>> >
>> > since the parser could very well accept another digit here.
>
> parsec2 did that, I don't kno
On 29 sep 2010, at 00:58, o...@cs.otago.ac.nz wrote:
>> Avoiding repeated additions:
>>
>> movingAverage :: Int -> [Float] -> [Float]
>> movingAverage n l = runSums (sum . take n $l) l (drop n l)
>> where n' = fromIntegral n
>> runSums sum (h:hs) (t:ts) = sum / n' : runSums (su
On 29/09/2010 07:33 PM, Steve Schafer wrote:
The issue isn't that there aren't a lot of Windows developers who have
an interest in Haskell+GUI development. The issue is that nearly every
Windows developer who looks into Haskell+GUI says, "This stuff sucks,"
and walks away, because they're intere
Hi Tom,
The Utrecht Haskell Compiler (UHC) is internally organized as a set of
compilers, for which you can configure the aspects you want. It is relatively
easy to extract such a particular combination and use it as a starting point.
Or you might install UHC itself and use the installed librar
Ryan Ingram gmail.com> writes:
> Haskell doesn't have true type functions; what you are really saying is
>
> instance Monad (\v -> Vect k (Monomial v))
>
Yes, that is exactly what I am trying to say. And since I'm not allowed to say
it like that, I was trying to say it using a type synonym par
On Wednesday 29 September 2010 23:02:02, Andrew Coppin wrote:
> So anyway, that's the problem. The solution is...
Two obvious solutions.
- stop using Windows and migrate to an OS where stuff works pretty much out
of the box (not going to happen a lot)
- start helping to make things work on Window
On Wednesday 29 September 2010 23:15:14, DavidA wrote:
> Ryan Ingram gmail.com> writes:
> > Haskell doesn't have true type functions; what you are really saying
> > is
> >
> > instance Monad (\v -> Vect k (Monomial v))
>
> Yes, that is exactly what I am trying to say. And since I'm not allowed
> t
It's hard. Here's a simple example:
type Foo f = f Int
class C (f :: (* -> *) -> *) where
thingy :: f [] -> f IO
-- Should this ever typecheck? I would say no; there's no way to
unify f [] with [Int].
callThingy :: [Int] -> IO Int
callThingy = thingy
-- but what if you say this?
instance C
On Wed, Sep 29, 2010 at 11:15 PM, DavidA wrote:
> Ryan Ingram gmail.com> writes:
>
>> Haskell doesn't have true type functions; what you are really saying is
>>
>> instance Monad (\v -> Vect k (Monomial v))
>>
>
> Yes, that is exactly what I am trying to say. And since I'm not allowed to say
> it
Andrew Coppin wrote:
> On 29/09/2010 07:33 PM, Steve Schafer wrote:
>> The issue isn't that there aren't a lot of Windows developers who have
>> an interest in Haskell+GUI development. The issue is that nearly every
>> Windows developer who looks into Haskell+GUI says, "This stuff sucks,"
>> and
These were enough to get me started:
http://www.haskell.org/haskellwiki/Opengl
http://haskell.forkio.com/com-examples
http://darcs.haskell.org/packages/Win32/examples/
Roderick
> Date: Wed, 29 Sep 2010 11:01:50 -0400
> From: cas...@istar.ca
> To: haskell-cafe@haskell.org
> Sub
> The organisers may put more detail on the contest website perhaps?
Will do, after I get home from ICFP. - Best, Johannes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
When I change the cabal file to say
preference: base >= 4
I still get, "you are using base 3.0 which is deprecated."
When I change the overall cabal profile, the error message still comes up.
It seems like some other part of the install process is controlling
the base version, besides the *.caba
On Thursday 30 September 2010 00:56:56, cas...@istar.ca wrote:
> When I change the cabal file to say
> preference: base >= 4
In the .cabal file of a package, that would belong in the build-depends.
> I still get, "you are using base 3.0 which is deprecated."
> When I change the overall cabal prof
On Wed, Sep 29, 2010 at 3:56 PM, wrote:
> When I change the cabal file to say
> preference: base >= 4
> I still get, "you are using base 3.0 which is deprecated."
> When I change the overall cabal profile, the error message still comes up.
> It seems like some other part of the install process is
Antoine and Christian:
Many thanks for your help on this thread.
(I am still digesting it; much appreciated; will post when I get it working.)
-- Peter
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-
On 09/29/2010 02:15 PM, DavidA wrote:
instance Monad (\v -> Vect k (Monomial v))
>
Yes, that is exactly what I am trying to say. And since I'm not allowed to say
it like that, I was trying to say it using a type synonym parameterised over v
instead.
Why not:
instance Monad ((->) Vect k (M
On 09/29/2010 09:13 PM, Alexander Solla wrote:
On 09/29/2010 02:15 PM, DavidA wrote:
instance Monad (\v -> Vect k (Monomial v))
>
Yes, that is exactly what I am trying to say. And since I'm not
allowed to say
it like that, I was trying to say it using a type synonym
parameterised over v
i
David,
Ryan Ingram wrote:
>>> Haskell doesn't have true type functions; what you are really saying
>>> is
>>>
>>> instance Monad (\v -> Vect k (Monomial v))
Daniel Fischer wrote:
> I think there was a theoretical reason why that isn't allowed (making type
> inference undecidable? I don't reme
Hi,
I was going over the Error Handling chapter in RWH and tried out this sample -
Prelude> :m Control.Exception
Prelude Control.Exception> let x=5 `div` 0
Prelude Control.Exception> let y=5 `div` 1
Prelude Control.Exception> handle (\_ -> putStrLn "Text") (print x)
:1:0:
Ambiguous type varia
On 30 September 2010 15:23, C K Kashyap wrote:
> Hi,
> I was going over the Error Handling chapter in RWH and tried out this sample -
>
> Prelude> :m Control.Exception
> Prelude Control.Exception> let x=5 `div` 0
> Prelude Control.Exception> let y=5 `div` 1
> Prelude Control.Exception> handle (\_
Hello fellow Haskellers,
(after failing (again) to send to the haskell list, I'm posting this
here. I've contacted the mailing list owner about this.)
I'm announcing the 0.4.0 release of the 'contstuff' monad transformer
library, an alternative to libraries like 'mtl', 'transformers' and
'monadL
Thanks Ivan,
>
> * Keep using old-style exceptions. With GHC 6.10 and 6.12, import
> Control.OldException instead of Control.Exception
> * Manually migrate the RWH code to new-style exceptions; there are two
> ways of doing this:
> - For production code, you should add explicit type signatures,
On 30 September 2010 16:46, C K Kashyap wrote:
>
> Could you please review the change I've done to Don Stewart's
> scripting example -
>
> run s = handle (fail . show) $ do
> (ih,oh,eh,pid) <- runInteractiveCommand s
> so <- hGetContents oh
> se <- hGetContents eh
> hClose ih
> ex <
61 matches
Mail list logo