[Haskell-cafe] ANN: data-textual: Human-friendly textual representations

2013-04-24 Thread Mikhail Vorozhtsov

Hello lists,

I'm pleased to announce the first release of data-textual[1], a library 
that provides human-friendly counterparts (called Printable/Textual) of 
the compiler-friendly Show/Read type classes. The library is intended to 
be used for printing and parsing of non-compound and non-polymorphic 
compound data (e.g. numbers, network and hardware addresses, date/time, 
etc).


A quick example (vs network-ip[2] library):

λ import Data.Maybe (fromJust)
λ import Data.Textual
λ import Network.IP.Addr

λ let x = fromString [dead::b:e:e:f]:123 :: Maybe Inet6Addr
λ x
Just (InetAddr {inetHost = ip6FromWords 0xdead 0x0 0x0 0x0 0xb 0xe 0xe 
0xf, inetPort = 123})

λ toString (fromJust x)
[dead::b:e:e:f]:123

λ let y = fromStringAs aNet4Addr 192.168.100.1/24
λ y
Just (netAddr (ip4FromOctets 192 168 100 1) 24)
λ toText (netPrefix $ fromJust y)
192.168.100.0

[1] http://hackage.haskell.org/package/data-textual
[2] http://hackage.haskell.org/package/network-ip

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Operations on functional graphs

2013-04-24 Thread Francesco Mazzoli
Hi list,

I’ve been lately thinking about how to implement an algorithm efficiently, and I
need a directed graph that can perform the following tasks:

  1. Finding the strongly connected components
  2. Condensing strongly connected components
  3. Contract single edges

The condensing shouldn’t prevent successive operations to work with the
condensed vertices (treating them all as the same), but should get rid of the
edges.

Point one is easy, for example as described in [1].  I’m wondering if a nice way
to implement the other two with functional structures has been described.  I’d
guess it would be a mix of a graph and disjoint sets data structure...

Thanks,
Francesco


[1]: Structuring Depth-First Search Algorithms in Haskell, by David King and
John Launchbury.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell compilation errors break the complexity encapsulation on DSLs

2013-04-24 Thread Alberto G. Corona
Maybe it is possible to do something In a google summer of code. Nothing as
sophisticated as  the Helium paper (Scripting the Type Inference
Process, but maybe a partial implementation of the techniques mentioned,
so that the development can be enhanced in the future.

Maybe some kind of  library that permits postprocessing of GHC errors
and/or the identification of points in the current type checker where some
kind of rules can be defined by the programmer can be the first step.


2013/4/23 Brent Yorgey byor...@seas.upenn.edu

 On Tue, Apr 23, 2013 at 12:49:59PM +0200, Alberto G. Corona  wrote:
  Hi
 
  I ever was worried about the barrier that the complexity of the Haskell
  errors impose to users of DSLs. Many DSLs look so simple that even
 someone
  without knowledge of Haskell can make use of them for some domains.
 
  However when the program is compiled then al the monsters of the
  deep appear in the surface: polymorphisms, undefined instances, type
 errors
  reported in a line produced by a type assumption in another,  etc. This
 is
  a problem for an industrial use of Haskell in the large scale. For
 obvious
  reasons.

 Indeed.  For example, in my experience this is a big problem for diagrams.

 
 
  The question: Is it possible to develop a GHC extension that attach (or
  prepend) such an explanation to the ghc error?
 
  Or any other alternative that carry out the same functionality.

 Surely it is possible.  I have wanted this too.  I guess the majority
 of the work would just be in coming up with a good, general design
 which is useful but not too difficult to implement.  If anyone wanted
 to undertake such a project I would be happy to contribute some ideas.

 -Brent

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Alberto.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-24 Thread Hans Höglund
Hi Conal,

Thank you for replying.

My aim is to find the simplest possible implementation of the semantics you 
describe in Push-pull FRP, so the denotational semantics are already in place. 
I guess what I am looking for is a simple translation of a denotational program 
into an imperative one. My intuition tells me that such a translation is 
possible, maybe even trivial, but I am not sure how to reason about 
correctness. 

While I like the idea of TCMs very much, they do not seem to be applicable for 
things that lack a denotation, such as IO. Maybe it is a question of how to 
relate denotational semantics to operational ones?

Hans


On 24 apr 2013, at 02:18, Conal Elliott wrote:

 Hi Hans,
 
 Do you have a denotation for your representation (a specification for your 
 implementation)? If so, it will likely guide you to exactly the right type 
 class instances, via the principle of type class morphisms (TCMs). If you 
 don't have a denotation, I wonder how you could decide what correctness means 
 for any aspect of your implementation.
 
 Good luck, and let me know if you want some help exploring the TCM process,
 
 -- Conal
 
 
 On Tue, Apr 23, 2013 at 6:22 AM, Hans Höglund h...@hanshoglund.se wrote:
 Hi everyone,
 
 I am experimenting with various implementation styles for classical FRP. My 
 current thoughts are on a continuation-style push implementation, which can 
 be summarized as follows.
 
  newtype EventT m r a= E { runE :: (a - m r) - m r - m r }
  newtype ReactiveT m r a = R { runR :: (m a - m r) - m r }
  type Event= EventT IO ()
  type Reactive = ReactiveT IO ()
 
 The idea is that events allow subscription of handlers, which are 
 automatically unsubscribed after the continuation has finished, while 
 reactives allow observation of a shared state until the continuation has 
 finished.
 
 I managed to write the following Applicative instance
 
  instance Applicative (ReactiveT m r) where
  pure a  = R $ \k - k (pure a)
  R f * R a = R $ \k - f (\f' - a (\a' - k $ f' * a'))
 
 But I am stuck on finding a suitable Monad instance. I notice the similarity 
 between my types and the ContT monad and have a feeling this similarity could 
 be used to clean up my instance code, but am not sure how to proceed. Does 
 anyone have an idea, or a pointer to suitable literature.
 
 Best regards,
 Hans
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing an embedded language that threads a global structure.

2013-04-24 Thread Ian Bloom
Incidentally I did find a solution that fits into the type system and also
produces the correct result. This was done by making the global parameter
change type as well at each lambda so that it becomes a function with the
same arrity as the term. Unfortunately to evaluate these terms the program
needs fork and do redundant work at every application of lam (so it's a
major hack), though it does give me some confidence that a real solution is
possible perhaps by using dependent types?:

lam :: ((g-(g,a)) - (g-(g',b))) - (g-(a-g',a-b))
lam = (\ f - \ g - (\x - fst $ (f (\ gv-(gv,x))) g,
  \y - snd $ (f (\ gv-(gv,y))) g ))

app :: (g-(a-g1,a-b)) - (g-(g,a)) - (g-(g1,b))
app = (\ eA eB - \ gz - let(gB, fB) = eB gz
  in let (lgA, lfA) = eA gB
  in (lgA fB, lfA fB) )

ext :: ((g1,a)-(g2,b))-(g0-(g1,a))-(g0-(g2,b))
ext = \f - \a - \g - f (a g)

idCounter :: Num g = (g,a) - (g, a)
idCounter = \(g, x) - (g+1, x)

-- Example terms
trmA = lam (\x - lam (\y - app x y))
trmB = (lam (\y - app trmC y))
trmC = (\g - (\c-g,\c-c+3))
trmD = (\g - (g,3))
trmE = app trmC trmD
trmF = (ext idCounter) trmD
trmG = app trmC (app trmC trmF)
trmH = app trmC trmE

---

Here's my original statement of the problem
http://hastebin.com/raw/bewiqihiyo
And here's all my code with new, http://hpaste.org/86273

Unfortunately, I don't know of a way to tell the compiler that essentially
the variables x and y in the lam function will always be applied to the
same value. Unfortunately, I've reached a limit of my understanding of how
pairs integrate with the type system in Haskell,
I've considered returning something other than a pair from my base function
(such as a function) but I have yet to figure that out.

Thanks for your insights,
Ian Bloom
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Duncan Coutts
On Sun, 2013-04-21 at 18:07 -0700, Edward Z. Yang wrote:
 Hello all, (cc'd stream fusion paper authors)
 
 I noticed that the current implementation of stream fusion does
 not support multiple-return stream combinators, e.g.
 break :: (a - Bool) - [a] - ([a], [a]).  I thought a little
 bit about how might one go about implement this, but the problem
 seems nontrivial. (One possibility is to extend the definition
 of Step to support multiple return, but the details are a mess!)
 Nor, as far as I can tell, does the paper give any treatment of
 the subject.  Has anyone thought about this subject in some detail?

I address it briefly in my thesis [1], Section 4.8.2. I think it's a
fundamental limitation of stream fusion.

It looks like fold and unfold fusion systems have dual limitations:
fold-based fusion cannot handle zip style functions, while unfold-based
fusion cannot handle unzip style functions. That is fold-based cannot
consume multiple inputs, while unfold-based cannot produce multiple
outputs.

I'll be interested to see in more detail the approach that Ben is
talking about. As Ben says, intuitively the problem is that when you've
got multiple outputs so you need to make sure that someone is consuming
them and that that consumption is appropriately synchronised so that you
don't have to buffer (buffering would almost certainly eliminate the
gains from fusion). That might be possible if ultimately the multiple
outputs are combined again in some way, so that overall you still have a
single consumer, that can be turned into a single lazy or eager loop.

[1]: http://code.haskell.org/~duncan/thesis.pdf

Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Bryan O'Sullivan
On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
duncan.cou...@googlemail.com wrote:

 I address it briefly in my thesis [1], Section 4.8.2. I think it's a
 fundamental limitation of stream fusion.


See also concat, where the naive fusion-based implementation has quadratic
performance:

concat :: [Text] - Text
concat txts = unstream (Stream.concat (List.map stream txts))

I've never figured out how to implement this with sensible characteristics
within the fusion framework.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Duncan Coutts
On Wed, 2013-04-24 at 10:56 -0700, Bryan O'Sullivan wrote:
 On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
 duncan.cou...@googlemail.com wrote:
 
  I address it briefly in my thesis [1], Section 4.8.2. I think it's a
  fundamental limitation of stream fusion.
 
 
 See also concat, where the naive fusion-based implementation has quadratic
 performance:
 
 concat :: [Text] - Text
 concat txts = unstream (Stream.concat (List.map stream txts))
 
 I've never figured out how to implement this with sensible characteristics
 within the fusion framework.

Well of course concatMap is another issue. I address that in section
4.8.3 :-)

Summary there is that I don't think it is a fundamental limitation, but
certainly we don't do it properly in practice now. I have a suggestion
in that section for how we might do it.

Duncan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-24 Thread Conal Elliott
Hi Hans.

I'm delighted to hear that you have a precise denotation to define
correctness of your implementation. So much of what gets called FRP these
days abandons any denotational foundation, as well as continuous time,
which have always been the two key properties of
FRPhttp://stackoverflow.com/a/5878525/127335for me.

I like your goal of finding a provably correct (perhaps correct by
construction/derivation) implementation of the simple denotational
semantics. I'm happy to give feedback and pointers if you continue with
this goal.

While I like the idea of TCMs very much, they do not seem to be applicable
 for things that lack a denotation, such as IO


I suppose so, although I'd say it the other way around: things that lack
denotation are not applicable for fulfilling denotational principles. Which
suggests to me that IO will not get you to your goal. Instead, I recommend
instead looking for a subset of imperative computation that suffices to
implement the denotation you want, but is well-defined denotationally and
tractable for reasoning. IO (general imperative computation) is neither,
which is why we have denotative/functional programming in the first place.

Regards, - Conal


On Wed, Apr 24, 2013 at 8:31 AM, Hans Höglund h...@hanshoglund.se wrote:

 Hi Conal,

 Thank you for replying.

 My aim is to find the simplest possible implementation of the semantics
 you describe in Push-pull FRP http://conal.net/papers/push-pull-frp/,
 so the denotational semantics are already in place. I guess what I am
 looking for is a simple translation of a denotational program into an
 imperative one. My intuition tells me that such a translation is possible,
 maybe even trivial, but I am not sure how to reason about correctness.

 While I like the idea of TCMs very much, they do not seem to be applicable
 for things that lack a denotation, such as IO. Maybe it is a question of
 how to relate denotational semantics to operational ones?

 Hans


 On 24 apr 2013, at 02:18, Conal Elliott wrote:

 Hi Hans,

 Do you have a denotation for your representation (a specification for your
 implementation)? If so, it will likely guide you to exactly the right type
 class instances, via the principle of type class 
 morphismshttp://conal.net/papers/type-class-morphisms/(TCMs). If you don't 
 have a denotation, I wonder how you could decide what
 correctness means for any aspect of your implementation.

 Good luck, and let me know if you want some help exploring the TCM process,

 -- Conal


 On Tue, Apr 23, 2013 at 6:22 AM, Hans Höglund h...@hanshoglund.se wrote:

 Hi everyone,

 I am experimenting with various implementation styles for classical FRP.
 My current thoughts are on a continuation-style push implementation, which
 can be summarized as follows.

  newtype EventT m r a= E { runE :: (a - m r) - m r - m r }
  newtype ReactiveT m r a = R { runR :: (m a - m r) - m r }
  type Event= EventT IO ()
  type Reactive = ReactiveT IO ()

 The idea is that events allow subscription of handlers, which are
 automatically unsubscribed after the continuation has finished, while
 reactives allow observation of a shared state until the continuation has
 finished.

 I managed to write the following Applicative instance

  instance Applicative (ReactiveT m r) where
  pure a  = R $ \k - k (pure a)
  R f * R a = R $ \k - f (\f' - a (\a' - k $ f' * a'))

 But I am stuck on finding a suitable Monad instance. I notice the
 similarity between my types and the ContT monad and have a feeling this
 similarity could be used to clean up my instance code, but am not sure how
 to proceed. Does anyone have an idea, or a pointer to suitable literature.

 Best regards,
 Hans

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-24 Thread Alberto G. Corona
If you are not looking for the full reactive formalism but to treat event
driven applications in a procedural ,sequential, imperative way (whatever
you may  call it) by means o continuations, then this is a good paper in
the context of web applications:

inverting back the inversion of control

http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.29.3112


2013/4/24 Conal Elliott co...@conal.net

 Hi Hans.

 I'm delighted to hear that you have a precise denotation to define
 correctness of your implementation. So much of what gets called FRP these
 days abandons any denotational foundation, as well as continuous time,
 which have always been the two key properties of 
 FRPhttp://stackoverflow.com/a/5878525/127335for me.

 I like your goal of finding a provably correct (perhaps correct by
 construction/derivation) implementation of the simple denotational
 semantics. I'm happy to give feedback and pointers if you continue with
 this goal.


 While I like the idea of TCMs very much, they do not seem to be applicable
 for things that lack a denotation, such as IO


 I suppose so, although I'd say it the other way around: things that lack
 denotation are not applicable for fulfilling denotational principles. Which
 suggests to me that IO will not get you to your goal. Instead, I recommend
 instead looking for a subset of imperative computation that suffices to
 implement the denotation you want, but is well-defined denotationally and
 tractable for reasoning. IO (general imperative computation) is neither,
 which is why we have denotative/functional programming in the first place.

 Regards, - Conal


 On Wed, Apr 24, 2013 at 8:31 AM, Hans Höglund h...@hanshoglund.se wrote:

 Hi Conal,

 Thank you for replying.

  My aim is to find the simplest possible implementation of the semantics
 you describe in Push-pull FRP http://conal.net/papers/push-pull-frp/,
 so the denotational semantics are already in place. I guess what I am
 looking for is a simple translation of a denotational program into an
 imperative one. My intuition tells me that such a translation is possible,
 maybe even trivial, but I am not sure how to reason about correctness.

 While I like the idea of TCMs very much, they do not seem to be
 applicable for things that lack a denotation, such as IO. Maybe it is a
 question of how to relate denotational semantics to operational ones?

 Hans


 On 24 apr 2013, at 02:18, Conal Elliott wrote:

 Hi Hans,

 Do you have a denotation for your representation (a specification for
 your implementation)? If so, it will likely guide you to exactly the right
 type class instances, via the principle of type class 
 morphismshttp://conal.net/papers/type-class-morphisms/(TCMs). If you don't 
 have a denotation, I wonder how you could decide what
 correctness means for any aspect of your implementation.

 Good luck, and let me know if you want some help exploring the TCM
 process,

 -- Conal


 On Tue, Apr 23, 2013 at 6:22 AM, Hans Höglund h...@hanshoglund.sewrote:

 Hi everyone,

 I am experimenting with various implementation styles for classical FRP.
 My current thoughts are on a continuation-style push implementation, which
 can be summarized as follows.

  newtype EventT m r a= E { runE :: (a - m r) - m r - m r }
  newtype ReactiveT m r a = R { runR :: (m a - m r) - m r }
  type Event= EventT IO ()
  type Reactive = ReactiveT IO ()

 The idea is that events allow subscription of handlers, which are
 automatically unsubscribed after the continuation has finished, while
 reactives allow observation of a shared state until the continuation has
 finished.

 I managed to write the following Applicative instance

  instance Applicative (ReactiveT m r) where
  pure a  = R $ \k - k (pure a)
  R f * R a = R $ \k - f (\f' - a (\a' - k $ f' * a'))

 But I am stuck on finding a suitable Monad instance. I notice the
 similarity between my types and the ContT monad and have a feeling this
 similarity could be used to clean up my instance code, but am not sure how
 to proceed. Does anyone have an idea, or a pointer to suitable literature.

 Best regards,
 Hans

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Alberto.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Fwd: How to do automatic reinstall of all dependencies?

2013-04-24 Thread capn.fre...@gmail.com


-db

- Forwarded message -
From: Captain Freako capn.fre...@gmail.com
Date: Tue, Apr 23, 2013 9:21 pm
Subject: How to do automatic reinstall of all dependencies?
To: haskell-cafe@haskell.org

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Gábor Lehel
On Wed, Apr 24, 2013 at 7:56 PM, Bryan O'Sullivan b...@serpentine.comwrote:

 On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
 duncan.cou...@googlemail.com wrote:

 I address it briefly in my thesis [1], Section 4.8.2. I think it's a
 fundamental limitation of stream fusion.


 See also concat, where the naive fusion-based implementation has quadratic
 performance:

 concat :: [Text] - Text
 concat txts = unstream (Stream.concat (List.map stream txts))

 I've never figured out how to implement this with sensible characteristics
 within the fusion framework.


If you could solve concat, might that also lead to be being able to do
without the Skip constructor? Skip was added explicitly to be able to
efficiently handle things like filter (without it the Step datatype is
exactly the base functor for lists), but if concat works, then filter p
can be expressed as concat . map (\x - if (p x) then [x] else []). Of
course, presumably filter isn't the only function that requires Skip, I
don't know what the others are. (Also of course solve and works are
intentionally fuzzy, with the point being that I don't know if solving
concat implies that the desirable properties would survive composition in
the suggested manner.)

-- 
Your ship was destroyed in a monadic eruption.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Dan Doel
Presumably concat also has to use skip, for the same reason as filter.
Otherwise it has to recursively process the outer stream until it gets to a
non-empty inner stream, which breaks the rule that only the final consumer
is recursive.

concat [[1,2,3],[4,5],[],[6,7]]

probably looks something like:

Yield 1, Yield 2, Yield 3, Skip, Yield 4, Yield 5, Skip, Skip, Yield 6,
Yield 7, Skip, Done

-- Dan



On Wed, Apr 24, 2013 at 6:52 PM, Gábor Lehel illiss...@gmail.com wrote:



 On Wed, Apr 24, 2013 at 7:56 PM, Bryan O'Sullivan b...@serpentine.comwrote:

 On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
 duncan.cou...@googlemail.com wrote:

 I address it briefly in my thesis [1], Section 4.8.2. I think it's a
 fundamental limitation of stream fusion.


 See also concat, where the naive fusion-based implementation has
 quadratic performance:

 concat :: [Text] - Text
 concat txts = unstream (Stream.concat (List.map stream txts))

 I've never figured out how to implement this with sensible
 characteristics within the fusion framework.


 If you could solve concat, might that also lead to be being able to do
 without the Skip constructor? Skip was added explicitly to be able to
 efficiently handle things like filter (without it the Step datatype is
 exactly the base functor for lists), but if concat works, then filter p
 can be expressed as concat . map (\x - if (p x) then [x] else []). Of
 course, presumably filter isn't the only function that requires Skip, I
 don't know what the others are. (Also of course solve and works are
 intentionally fuzzy, with the point being that I don't know if solving
 concat implies that the desirable properties would survive composition in
 the suggested manner.)

 --
 Your ship was destroyed in a monadic eruption.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Gábor Lehel
Ah, good point.

On Thu, Apr 25, 2013 at 1:06 AM, Dan Doel dan.d...@gmail.com wrote:

 Presumably concat also has to use skip, for the same reason as filter.
 Otherwise it has to recursively process the outer stream until it gets to a
 non-empty inner stream, which breaks the rule that only the final consumer
 is recursive.

 concat [[1,2,3],[4,5],[],[6,7]]

 probably looks something like:

 Yield 1, Yield 2, Yield 3, Skip, Yield 4, Yield 5, Skip, Skip, Yield
 6, Yield 7, Skip, Done

 -- Dan



 On Wed, Apr 24, 2013 at 6:52 PM, Gábor Lehel illiss...@gmail.com wrote:



 On Wed, Apr 24, 2013 at 7:56 PM, Bryan O'Sullivan b...@serpentine.comwrote:

 On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
 duncan.cou...@googlemail.com wrote:

 I address it briefly in my thesis [1], Section 4.8.2. I think it's a
 fundamental limitation of stream fusion.


 See also concat, where the naive fusion-based implementation has
 quadratic performance:

 concat :: [Text] - Text
 concat txts = unstream (Stream.concat (List.map stream txts))

 I've never figured out how to implement this with sensible
 characteristics within the fusion framework.


 If you could solve concat, might that also lead to be being able to do
 without the Skip constructor? Skip was added explicitly to be able to
 efficiently handle things like filter (without it the Step datatype is
 exactly the base functor for lists), but if concat works, then filter p
 can be expressed as concat . map (\x - if (p x) then [x] else []). Of
 course, presumably filter isn't the only function that requires Skip, I
 don't know what the others are. (Also of course solve and works are
 intentionally fuzzy, with the point being that I don't know if solving
 concat implies that the desirable properties would survive composition in
 the suggested manner.)

 --
 Your ship was destroyed in a monadic eruption.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





-- 
Your ship was destroyed in a monadic eruption.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Request for help with shared object link failure, involving relocation and -fPIC.

2013-04-24 Thread Captain Freako
Can anyone help me solve this link failure?

ghc -o libami.so -shared -package parsec -lHSrts -lm -lffi -lrt AMIParse.o
AMIModel.o ami_model.o ExmplUsrModel.o Filter.o
/usr/bin/ld: /usr/lib/ghc-7.4.2/libHSrts.a(RtsAPI.o): relocation
R_X86_64_32S against `ghczmprim_GHCziTypes_Czh_con_info' can not be used
when making a shared object; recompile with -fPIC
/usr/lib/ghc-7.4.2/libHSrts.a: could not read symbols: Bad value
collect2: error: ld returned 1 exit status

Thanks!
-db
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-24 Thread Conal Elliott
Hi Jared,

Oh -- does Elm have a denotational semantics? I haven't heard of one. I
just now skimmed the informal description of the Signal
typehttp://elm-lang.org/docs/Signal/Signal.elm,
and from the reference to updates in the description of merge, it sound
like whatever semantics it might have, it couldn't be function-of-time. I'm
intrigued with your interpretation. I wonder what it could mean for an
event to be a derivative, especially partial one, and for arbitrary types.

-- Conal


On Wed, Apr 24, 2013 at 1:48 PM, earl obscure theanswertoprobl...@gmail.com
 wrote:

 Hi Conal,


 Caveat pre-emptor I'm new to haskell, frp, etc ..  anyway how I was
 interpreting Elm's Eventbased strict FRP, was that each event was the
 partial derivative of the continuous time variable,  and then since it was
 being strict, it would evaluate the tangent line or state of the system at
 that point, only update when necessary.


 Now related to Continuations, this is something I've been thinking about
 as well,but haven't gotten very far; apparently cont monad, and comonad are
 closely related.  I was hoping to use the comonad rules, extend/duplicate
 to encode different continuations paths, and then extract when, a
 continuation path is chosen.  Was hoping maybe the analog would be PDE's,
 or something more general than my interpretation of Elm's FRP.

 These are just random thoughts that I wanted to get out. Thanks.

 Jared Nicholson.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Instances for continuation-based FRP

2013-04-24 Thread Conal Elliott
The intuition intrigues me. If, upon inspection, it survives morphs into
something else, I'd like to hear about it.

Good luck! -- Conal

The object of mathematical rigor is to sanction and legitimize the
conquests of intuition, and there was never any other object for it. -
Jacques Hadamard

I call intuition cosmic fishing. You feel a nibble, then you've got to
hook the fish. -- Buckminster Fullero



On Wed, Apr 24, 2013 at 7:26 PM, earl obscure theanswertoprobl...@gmail.com
 wrote:


 His description of the different frp approaches starts at section 2.1 of
 the thesis.
 http://www.testblogpleaseignore.com/wp-content/uploads/2012/04/thesis.pdfThen 
 in 3.1 describes implementation of discrete signals. I don't think he
 gives a denotational semantics.
 I was thinking, the event, is the derivative of the specific continuous
 signal it corresponds to, all other continuous signals of the system held
 equal.  Applying the partial derivative, is like sampling, or discrete time
 stepping.  But it is samplying the entire state, or multivariate structure
 not just the specific symbol. This made more sense unarticulated.  I'll
 need to think a bit.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe