hi,
if been thinking about an haskell interpreter to, because of erlang's
otp. its syntax is a mess, but its scalability is win.
since erlang runs in its vm ("interpreted") is there a need for a real
haskell interpreter, or can there be a compiled haskell/otp with
hotswapping, scaling and st
Thanks Wren,
Thanks Dave ... a quick question though could you point me to an example
where I could build up my own in place modifiable data structure in Haskell
without using any standard library stuff?
For example, if I wanted an image representation such as this
[[(Int,Int.Int)]] - basically a
I'm pleased to announce a new release of highlighting-kate [1],
a syntax highlighting library based on syntax definitions from
the kate editor.
!! Important note !! The new release uses new, two-letter class names in
its HTML output. If you use highlighting-kate, you will need to
update your css f
Andrew Webb wrote:
Because, at the basic level all of the experiments share this type of
data, it seems that I should be able to write analysis functions that
work for any experiment. However, the experiments differ in the
stimuli used, and associated with each stimulus set is a set of
"milestone
Dear all,
besides good ambitions in many other areas, it is interesting to see
that a great number of present Haskell projects is run by a very small
number of persons and even some parts of the usual developer's toolkit,
like e.g. Haddock, seem to contribute to it.
Has the Haskell culture p
begin Mike Dillon quotation:
> begin Vo Minh Thu quotation:
> > I guess it is short because you make use of second... so you can
> > define second' for your B data type, or make B an instance of Arrow.
>
> I don't think that's the case. The code for "f" is making use of the
> Arrow instance for (-
Oscar Finnsson wrote:
Anyone made a module/package that solves this problem already? I
cannot be the first that needs generic type safe conversion... .
There's a restricted version in logfloat:Data.Numer.RealToFrac[1] which
generalizes the Prelude's realToFrac to improve performance and correc
C K Kashyap wrote:
Thanks Daniel,
Better refactorability.
If you're using monadic style, changing from, say,
State Thing
to
StateT Thing OtherMonad
or from
StateT Thing FirstMonad
to
StateT Thing SecondMonad
typically requires only few changes. Explicit state-passing usually
requires more cha
Don Stewart writes:
> lazycat.manatee:
>> Hi all,
>>
>> I'm research to build a hot-swap Haskell program to developing itself in
>> Runtime, like Emacs.
>>
>> Essentially, Yi/Xmonad/dyre solution is "replace currently executing"
>> technology:
>>
>>re-compile new code with new binary entry
Jake McArthur wrote:
On 07/15/2010 05:33 PM, Victor Gorokhov wrote:
From the docs, lookup is O(min(n,W))
Actually worse than O(log n).
Perhaps I am misunderstanding you, but O(min(n,W)) is either better than
or the same as O(log n), depending on how you look at things, but I
don't see any w
Patrick Browne wrote:
Heinrich Apfelmus wrote:
3) Not sure what you mean by proof theoretic semantics. Apparently, the
trace of any program execution like, say
product [1..5] -> 1 * product [2..5] -> .. -> 120
is a proof that the initial and the final expression denote the same value.
The
On 07/15/2010 05:33 PM, Victor Gorokhov wrote:
Thanks for an example! Probably, one can think about using Arrays
instead of Map or IntMap in order to achieve 'true' O(1) in pure. But
I suppose that there are some trouble with array expanding. Or
somebody would already make it.
Pure arrays hav
Hi there haskellers,
I have thoroughly confused myself with type-classes in a haskell
system I am writing, and I was wondering if anyone had some useful
suggestions to get me out of my mess. I apologise if this is all long
and rambling, but that maybe why I can't solve it...
The system itself per
lazycat.manatee:
> Hi all,
>
> I'm research to build a hot-swap Haskell program to developing itself in
> Runtime, like Emacs.
>
> Essentially, Yi/Xmonad/dyre solution is "replace currently executing"
> technology:
>
>re-compile new code with new binary entry
>
>when re-compile succe
Hi all,
I'm research to build a hot-swap Haskell program to developing itself in
Runtime, like Emacs.
Essentially, Yi/Xmonad/dyre solution is "replace currently executing"
technology:
re-compile new code with new binary entry
when re-compile success
$ do
save state bef
Mark Lentczner writes:
> Will this be a problem for anyone? On one's own machine, I imagine we
> can come up with a simple script that will just rebuild all the
> Haddock docs and that will take care of it.
Seeing as how some versions of Haddock can't link with each other
already, I don't see th
Alexander Solla writes:
> On Jul 15, 2010, at 6:49 PM, Jason Dagit wrote:
>
>> Everyone has their own branch of everything they contribute to,
>> listed right on the website? This is inline with another idea I've
>> heard where we'd have a 'stable' hackage and 'unstable/dev'
>> versions. But,
On Fri, Jul 16, 2010 at 11:49 AM, Jason Dagit wrote:
>
>
> On Thu, Jul 15, 2010 at 5:54 PM, Mark Wotton wrote:
>>
>> Ideally, I'd like to be able to say something like "cabal install
>> my-hacked-package --as original-package" - are there fundamental
>> reasons that wouldn't be possible, or a bad
Brandon S Allbery KF8NH wrote:
wren is half right: at the level of Unixy APIs (and this includes anything
that goes on in a Terminal window and anything that you will be doing from
Haskell) you use UTF8, but OSX APIs --- that is, Carbon and Cocoa --- use
UTF16. So for the purposes of ghc/jhc OS
On Jul 15, 2010, at 6:49 PM, Jason Dagit wrote:
Everyone has their own branch of everything they contribute to,
listed right on the website? This is inline with another idea I've
heard where we'd have a 'stable' hackage and 'unstable/dev'
versions. But, how does this work for resolving
On Thu, Jul 15, 2010 at 5:54 PM, Mark Wotton wrote:
> Hello all,
>
> I've recently had problems with haskell-src-meta. While it's a great
> package, it doesn't currently compile on GHC 6.12, and Matt Morrow
> doesn't seem to be around to push the version that does to Hackage.
> Our "one-world" ap
begin Vo Minh Thu quotation:
> I guess it is short because you make use of second... so you can
> define second' for your B data type, or make B an instance of Arrow.
I don't think that's the case. The code for "f" is making use of the
Arrow instance for (->):
second :: Arrow a => a
Hello all,
I've recently had problems with haskell-src-meta. While it's a great
package, it doesn't currently compile on GHC 6.12, and Matt Morrow
doesn't seem to be around to push the version that does to Hackage.
Our "one-world" approach with cabal seems to discourage forking as a
casual act, so
Generics can help. But they are much slower than pattern matching.
{-# LANGUAGE DeriveDataTypeable #-}
import Data.Generics
import Control.Monad.State
type A = ( Int, String )
data B = B Int String deriving ( Show, Typeable, Data )
f :: ( Typeable a, Data d ) => [ a ] -> d -> d
f s = changeFiel
One of the problems is that the anchors that Haddock
currently generate aren't always legal in HTML, XHTML,
or XML. I'd like to fix the anchor generation so that they
are. If I do, then links between old and new generated
Haddock pages will land on the right page, but won't
always get to the r
Thanks for an example! Probably, one can think about using Arrays
instead of Map or IntMap in order to achieve 'true' O(1) in pure. But
I suppose that there are some trouble with array expanding. Or
somebody would already make it.
Pure arrays have O(n) modification time.
From the docs, lo
2010/7/15 Alexey Karakulov :
> I wonder if pattern matching could be less verbose. Maybe this sounds weird,
> but here is example of what I mean:
>
>> type A = (Int, String)
>>
>> f :: String -> A -> A
>> f s (i,s') = (i, s ++ s')
>>
>> data B = B Int String deriving Show
>>
>>g :: String -> B -> B
On Wed, Jul 14, 2010 at 11:43:45AM -0700, Thomas DuBuisson wrote:
> Vincent said:
> > couple of comments around the hashes interface:
> >
> > * updateCtx works on blockLength, instead of working on arbitrary size...
>
> So for performance reasons you seem to prefer Semantics 1.2?
>
> """
> 1.2 Mu
I wonder if pattern matching could be less verbose. Maybe this sounds weird,
but here is example of what I mean:
> type A = (Int, String)
>
> f :: String -> A -> A
> f s (i,s') = (i, s ++ s')
>
> data B = B Int String deriving Show
>
>g :: String -> B -> B
>g s (B i s') = B i $ s ++ s'
Types A/B
Thanks for the great feedback. The bijective example was especially interesting.
While reading "Fun with Type Functions" I notices GNum as an
interesting alternative to the Num type class but I couldn't find any
such package on hackagedb. Do anyone know if there is anything like
GNum on hackagedb?
On Thu, Jul 15, 2010 at 10:34 AM, C K Kashyap wrote:
> Thanks David for the detailed explanation.
>
> A couple of quick clarifications -
>
> 1. Even the "invisible" state that gets modified during the monadic
> evaluation is referred to as side effect right?
>
If the state is free of types that
Thanks David for the detailed explanation.
A couple of quick clarifications -
1. Even the "invisible" state that gets modified during the monadic
evaluation is referred to as side effect right?
2. I am a little unclear about "in-place" - does pure Haskell let one do
such a thing- or does it nee
Given a suitable definition for Vector2 (i.e., a 2D vector with the
appropriate classes), it is delightfully trivial to implement de
Casteljau's algorithm:
de_Casteljau :: Scalar -> [Vector2] -> [[Vector2]]
de_Casteljau t [p] = [[p]]
de_Casteljau t ps = ps : de_Casteljau t (zipWith (line t) ps
Vo Minh Thu wrote:
Found it:
http://hackage.haskell.org/package/repr
Between this and simple-reflect, it looks like Hackage has got it covered.
Thanks guys.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/lis
Stephen Tetley wrote:
On 14 July 2010 22:37, Andrew Coppin wrote:
(The small problem with the approach above, of course, is that as soon as
the function wants to do comparisons or take flow control decisions, you've
got trouble. It's not impossible to solve, but it *is* a lot of work...)
Thanks Daniel,
Better refactorability.
> If you're using monadic style, changing from, say,
> State Thing
> to
> StateT Thing OtherMonad
>
> or from
> StateT Thing FirstMonad
> to
> StateT Thing SecondMonad
>
> typically requires only few changes. Explicit state-passing usually
> requires more cha
Vo Minh Thu wrote:
Why not make some kinf of AST and pretty-print it ?
Yes, that's the logical next step. (And I've already coded it once. The
example code was just to put across what I'm trying to do.)
Also you can use
-XOverloadedStrings to write "x" + "y" instead of Dye "x" + Dye "y".
On Thu, Jul 15, 2010 at 9:02 AM, C K Kashyap wrote:
> Hi,
> I looked at State Monad yesterday and this question popped into my mind.
> From what I gather State Monad essentially allows the use of Haskell's do
> notation to "invisibly" pass around a state. So, does the use of Monadic
> style fetch
On Thu, Jul 15, 2010 at 01:20:11PM +0100, Pasqualino Titto Assini wrote:
> Many thanks for the explanation.
>
> But I thought that GHC always derives the most generic type, why does
> it fix my 'a' to 'Int' ?
Note that this type
evalAST2 :: forall a. (Expr a -> IO()) -> AST -> IO ()
means tha
On Thu, Jul 15, 2010 at 12:42:41AM +0100, Thomas Schilling wrote:
>
> simplifications are possible. To make this efficient, the solver also
> regularly canonicalises constraints. E.g., function symbols go to the
> left and constructors to the right.
One minor correction: the canonicalisation of
On Thursday 15 July 2010 18:02:47, C K Kashyap wrote:
> Hi,
> I looked at State Monad yesterday and this question popped into my mind.
>
> >From what I gather State Monad essentially allows the use of Haskell's
> > do
>
> notation to "invisibly" pass around a state. So, does the use of Monadic
> st
On Wed, Jul 14, 2010 at 4:42 PM, Thomas Schilling
wrote:
> The latest work is OutsideIn(X):
> http://www.haskell.org/haskellwiki/Simonpj/Talk:OutsideIn
>
> This is quite long paper. It describes a framework for
> constraint-based type inference and then instantiates it with a
> constraint solver
Hi,
I looked at State Monad yesterday and this question popped into my mind.
>From what I gather State Monad essentially allows the use of Haskell's do
notation to "invisibly" pass around a state. So, does the use of Monadic
style fetch us more than syntactic convenience?
Again, if I understand cor
I've been re-working on the Haddock HTML back end to get it to generate
"semantic markup" and legal XHTML.
One of the problems is that the anchors that Haddock currently generate aren't
always legal in HTML, XHTML, or XML. I'd like to fix the anchor generation so
that they are. If I do, then li
On Thu, Jul 15, 2010 at 9:20 AM, Pasqualino "Titto" Assini
wrote:
> Many thanks for the explanation.
>
> But I thought that GHC always derives the most generic type, why does
> it fix my 'a' to 'Int' ?
Inferring the type of higher ranked functions is problematic, so GHC
never does this by itself.
On 07/15/2010 02:30 AM, Stephen Tetley wrote:
2010/7/15 Jake McArthur:
On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
You can implement pure pointers on top of Data.Map with O(log n) time
Or on top of Data.IntMap with O(1) time. ;)
Unlikely...
From the docs, lookup is O(min(n,W))
Exact
Heinrich Apfelmus wrote:
>
> Lambda calculus is the basis for all three types of semantics:
>
> 1) Call-by-need (usually, implementations of Haskell are free to choose
> other evaluation strategies as long as the denotational semantics match)
>
> 2) The denotational semantics of a lambda calcul
Many thanks for the explanation.
But I thought that GHC always derives the most generic type, why does
it fix my 'a' to 'Int' ?
I have another question, now that I know how to pass a generic
continuation to evalAST I thought that I could use it to evaluate a
more complex language:
{-# LANGUAGE
GHC tries to infer the following type for evalAST2:
evalAST2 :: forall a. (Expr a -> IO()) -> AST -> IO ()
However when the type of 'a' has been found in the first alternatives:
evalAST2 k (IntA i) = k $ Lit i
it is fixed to Int. Then the 'a' doesn't match the type (String) found
in the other a
2010/7/15 Sergey Mironov :
> 2010/7/15 Serguey Zefirov :
>> 2010/7/14 Sergey Mironov :
>>> Hi cafe! I have a question of C-to-Haskell type:)
>>>
>>> Imagine web application wich allows users to browse some shared
>>> filesystem located at the server.
>>> Application stores every users's position wi
15 июля 2010 г. 2:01 пользователь Victor Gorokhov написал:
> You can implement pure pointers on top of Data.Map with O(log n) time:
>
> {-# LANGUAGE ExistentialQuantification #-}
> import Data.Map ( Map )
> import qualified Data.Map as Map
> import Data.Typeable
> import Control.Monad.State
> impo
Hi,
can anyone please explain why in the following code evalAST compiles
while evalAST2 doesn't?:
Is that because the polymorphic function k is specialised in two
different ways in evalAST while in evalAST2 it is constrained to be
the same function?
{-# LANGUAGE GADTs #-}
test = evalAST (TxtA "
2010/7/15 Serguey Zefirov :
> 2010/7/14 Sergey Mironov :
>> Hi cafe! I have a question of C-to-Haskell type:)
>>
>> Imagine web application wich allows users to browse some shared
>> filesystem located at the server.
>> Application stores every users's position within that filesystem
>> (current di
Patrick Browne wrote:
In Haskell what roles are played by 1)lambda calculus and 2) equational
logic? Are these roles related?
Thanks for your clear and helpful responses.
I am aware that this question can lead to into very deep water.
I am comparing Haskell with languages based on equational lo
2010/7/15 Vo Minh Thu :
> 2010/7/14 Vo Minh Thu :
>> 2010/7/14 Andrew Coppin :
>>> I'm trying to write a function that builds a series of results in a very
>>> complicated way. Eventually I ended up writing things like
>>>
newtype Dye = Dye String deriving (Eq, Show)
instance Num Dye
Corey
| On 14 July 2010 18:39, Corey O'Connor wrote:
| > I believe I have run headlong into issue #3064 in ghc
| > (http://hackage.haskell.org/trac/ghc/ticket/3064). All I think I know
| > is this:
| > * this is a performance issue with the system used to solve type
| constraints.
| > * the solve
On 14 July 2010 22:37, Andrew Coppin wrote:
>
> (The small problem with the approach above, of course, is that as soon as
> the function wants to do comparisons or take flow control decisions, you've
> got trouble. It's not impossible to solve, but it *is* a lot of work...)
>
Hi Andrew
You coul
Stephen Tetley writes:
> 2010/7/15 Jake McArthur :
>> On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
>>>
>>> You can implement pure pointers on top of Data.Map with O(log n) time
>>
>> Or on top of Data.IntMap with O(1) time. ;)
>
> Unlikely...
>
>>From the docs, lookup is O(min(n,W))
Yeah, I wa
On Thu, Jul 15, 2010 at 4:30 AM, Stephen Tetley
wrote:
> 2010/7/15 Jake McArthur :
>> On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
>>>
>>> You can implement pure pointers on top of Data.Map with O(log n) time
>>
>> Or on top of Data.IntMap with O(1) time. ;)
>
> Unlikely...
>
> >From the docs, l
2010/7/15 Jake McArthur :
> On 07/14/2010 05:01 PM, Victor Gorokhov wrote:
>>
>> You can implement pure pointers on top of Data.Map with O(log n) time
>
> Or on top of Data.IntMap with O(1) time. ;)
Unlikely...
>From the docs, lookup is O(min(n,W))
___
60 matches
Mail list logo