On Tue, Sep 18, 2012 at 8:39 PM, Dan Doel wrote:
> On Tue, Sep 18, 2012 at 11:19 PM, Ryan Ingram
> wrote:
> > Fascinating!
> >
> > But it looks like you still 'cheat' in your induction principles...
> >
> > ×-induction : ∀{A B} {P : A × B → Set}
&
ypes (although, I've been informed that sigma was
> novel, it not being a Simple Type), but haven't figured out natural
> numbers yet (I haven't actually studied the second paper above, which
> I was pointed to recently).
>
> -- Dan
>
> On Tue, Sep 18, 2012 at 5:4
Oleg, do you have any references for the extension of lambda-encoding of
data into dependently typed systems?
In particular, consider Nat:
nat_elim :: forall P:(Nat -> *). P 0 -> (forall n:Nat. P n -> P (succ
n)) -> (n:Nat) -> P n
The naive lambda-encoding of 'nat' in the untyped lambda-calc
The problem is that the function 'element' is ambiguous, for the reasons
MigMit pointed out.
The standard solution to this problem is to add a dummy argument to fix the
type argument to the type function:
data Proxy a = Proxy
class ... => ReplaceOneOf full where
type Item full :: *
--
Not exactly what you asked for, but...
filter (uncurry somePredicate) $ (,) <$> list1 <*> list2
does the job.
Using only applicative operations, it's impossible to affect the 'shape' of
the result--this is the difference in power between applicative and monad.
-- ryan
On Wed, Sep 12, 20
ngly recommend *not* doing it this way :)
-- ryan
On Mon, Sep 10, 2012 at 4:03 PM, Ryan Ingram wrote:
> From the point of view of the language, Message () and Message Int and
> Message Player are all completely distinct types and may have different
> behavior--there's no way for it
>From the point of view of the language, Message () and Message Int and
Message Player are all completely distinct types and may have different
behavior--there's no way for it to "know" that they all have the same
representation that only contains a String.
The derived Typeable instance for "Messa
System Fc has another name: "GHC Core". You can read it by running 'ghc
-ddump-ds' (or, if you want to see the much later results after
optimization, -ddump-simpl):
For example:
NonGADT.hs:
{-# LANGUAGE TypeFamilies, ExistentialQuantification, GADTs #-}
module NonGADT where
data T a = (a ~ ()
Also, I have to admit I was a bit handwavy here; I meant P in a
metatheoretic sense, that is "P(a) is some type which contains 'a' as a
free variable", and thus the 'theorem' is really a collection of theorems
parametrized on the P you choose.
For example, P(a) could be "Show a & a -> Int"; in tha
It seems really hard to solve this, since the type checker works before
instance selection has had a chance to do anything.
Instead of looking at the instance declaration, look at the use site:
lift x
expects the argument to have type
x :: t m a
for some t :: (* -> *) -> * -> *, m :: * -
In classical logic A -> B is the equivalent to ~A v B
(with ~ = not and v = or)
So
(forall a. P(a)) -> Q
{implication = not-or}
~(forall a. P(a)) v Q
{forall a. X is equivalent to there does not exist a such that X doesn't
hold}
~(~exists a. ~P(a)) v Q
{double negation elimination}
On Mon, Aug 13, 2012 at 6:53 PM, Alexander Solla wrote:
> In a classical logic, the duality is expressed by !E! = A, and !A! = E,
> where E and A are backwards/upsidedown and ! represents negation. In
> particular, for a proposition P,
>
> Ex Px <=> !Ax! Px (not all x's are not P)
> and
> Ax Px <
On Tue, Aug 14, 2012 at 1:04 AM, Евгений Пермяков wrote:
> Your idea looks _much_ better from code clarity point of view, but it's
> unclear to me, how to deal with it internally and in error messages. I'm
> not a compiler guy, though.
>
How to deal with it internally: It's pretty easy, actually
On Mon, Aug 13, 2012 at 12:30 PM, Jay Sulzberger wrote:
> Does Haskell have a word for "existential type" declaration? I
> have the impression, and this must be wrong, that "forall" does
> double duty, that is, it declares a "for all" in some sense like
> the usual "for all" of the Lower Predica
> But it would be in line with <- bindings in the do notation, so maybe it
wouldn't feel so wrong.
I was about to post this exact example.
do
x <- return 1
x <- return x
return x
seems to work just fine (the answer is 1). I'd even be ok with =-in-do
being non-recursive like <-
-- ryan
When I was implementing a toy functional languages compiler I did away with
precedence declarations by number and instead allowed the programmer to
specify a partial order on declarations; this seems to be a much cleaner
solution and avoids arbitrary precedences between otherwise unrelated
operator
Oops, forgot my references
[1] Original post:
http://www.twanvl.nl/blog/haskell/cps-functional-references
[2] polymorphic update support: http://r6.ca/blog/20120623T104901Z.html
[3] another post about these:
http://comonad.com/reader/2012/mirrored-lenses/
On Fri, Aug 3, 2012 at 1:53 PM, Ryan
On Fri, Aug 3, 2012 at 10:11 AM, Jonathan Geddes
wrote:
> The nice part about the SEC functions is that
> they compose as regular functions. Lenses are
> super powerful in that they form a category.
> Unfortunately using categories other than
> functions feels a tad unwieldy because you
> have to
Actually, looking at the docs, I'm not sure if case expressions work on
unboxed ints; you may need
addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) -> (I# s, c /=# 0#)
which is somewhat simpler anyways.
-- ryan
On Tue, Jul 31, 2012 at 1:56 AM, Ryan Ingram wrote:
> Sur
Sure, but it's easy to roll your own from those primitives:
{-# LANGUAGE MagicHash, UnboxedTuples #-}
import GHC.Exts
addCarry :: Int -> Int -> (Int, Bool)
addCarry (I# x) (I# y) = case addIntC# x y of
(# s, c #) -> case c of
0# -> (I# s, False)
_ -> (I# s, True)
or someth
A couple typos:
instance Monad Replacer1 where
->
instance Monad (Replacer1 k) where
instance Monad Replacer2 k where
->
instance Monad (Replacer2 k) where
I haven't tested any of this code, so you may have to fix some minor type
errors.
On Mon, Jul 30, 2012 at 10:38 PM, Ryan In
To take this a step further, if what you really want is the syntax sugar
for do-notation (and I understand that, I love sweet, sweet syntactical
sugar), you are probably implementing a Writer monad over some monoid.
Here's two data structures that can encode this type;
data Replacer1 k a = Replac
I'm not sure I totally understand your question about 'unpacking' an MVar,
but I'm going to assume you mean data structures that use the {-# UNPACK
#-} pragma, like in Control.Concurrent.Future [1] and
Control.Concurrent.NamedLock [2].
Here is how MVar is defined in GHC [3]:
data MVar a = MVar
Generally the way this is done in Haskell is that the interface to the type
is specified in a typeclass (or, alternatively, in a module export list,
for concrete types), and the axioms are specified in a method to be tested
in some framework (i.e. QuickCheck, SmallCheck, SmartCheck) which can
autom
With apologies to Jim Coplien :)
I've been seeing this pattern in a surprising number of instance
definitions lately:
instance (a ~ ar, b ~ br) => Mcomp a ar b br [1]
instance (b ~ c, CanFilterFunc b a) => CanFilter (b -> c) a [2]
The trick is that since instance selection is done entirely on th
My completely off-the-cuff guess is that
a a b b
isn't considered more or less specific than
(x -> a) ar (x -> b) br
since they both apply some constraint on the types. For example, it's not
immediately clear that the first instance can't be used for (x -> a) (x ->
a) (x -> b) (x -> b)
Wh
The difference is that foldl *must* produce the entire list of thunks, even
if f is lazy in its first argument.
There's no foldl that can perform better given a sufficiently-lazy f; given
head = foldr go fail where
go x y = x
fail = error "head: empty list"
head [a,b,c,d]
= foldr go fail
It doesn't work like that by default, and here is why:
-- an infinite tree of values
data InfTree a = Branch a (InfTree a) (InfTree a)
buildTree :: Num a => STRef s a -> ST s (InfTree a)
buildTree ref = do
n <- readSTRef ref
writeSTRef ref $! (n+1)
left <- buildTree ref
right <- b
Another option is to reify the type so that you can get it back somehow.
Here's a few diffs to your file (I've attached the full code):
A new type:
data Typed f where
TDouble :: f Double -> Typed f
TBool :: f Bool -> Typed f
runT :: (f Double -> a) -> (f Bool -> a) -> Typed f -> a
runT k _
For simple datatypes like this, GHC can derive the Functor implementation
for you:
{-# LANGUAGE DeriveFunctor #-}
data ExprF r =
deriving (..., Functor)
See http://www.haskell.org/ghc/docs/7.0.4/html/users_guide/deriving.html
-- ryan
On Fri, Apr 27, 2012 at 5:40 AM, Stefan Holdermans
A concurring opinion here, and an example.
iff :: Bol -> a -> a -> a
iff True x _ = x
iff False _ x = x
f, g :: Bool -> Bool
f x = x
g x = iff x True False
Are these two functions equal? I would say yes, they are. Yet once you
can pattern match on functions, you can easily tell these functions
the expressions above, "fac x" doesn't terminate
and instead gives x * (x-1) * (x-1-1) * ... forever. Other versions (like
the version in this thread with Num (e -> a)) turn fac into a function that
always returns bottom.
-- ryan
On Tue, Mar 20, 2012 at 12:02 PM, Ryan
This instance can be made more general without changing the code; change
the first line to
instance Num a => Num (e -> a) where
I think this version doesn't even require FlexibleInstances.
This lets you do
f x = if x then 2 else 3
g x = if x then 5 else 10
-- f + g = \x -> if x then 7 else 13
You can emulate mutation with at most O(log(n)) penalty using a map. Given
that memory is of fixed size, log2(n) <= 64, so for "real-world" programs
this becomes O(1). So any program you can implement using mutation can be
implemented in a pure language with the same big-O running time (but much
On Sun, Mar 11, 2012 at 8:38 PM, E R wrote:
> A pure function can allocate and modify memory as long as a) it never
> returns a reference to the memory or b) it never again modifies the
> memory once it returns (i.e. it returns an immutable object).
>
That's a reasonable first approximation to t
data Common = ...
data A = ...
data B = ...
data C = ...
data Super =
SubA { commonFields :: Common, getA :: A }
| SubB { commonFields :: Common, getB :: B }
| SubC { commonFields :: Common, getC :: C }
foldWithSubtype :: (A -> r) -> (B -> r) -> (C -> r) -> Super -> r
foldWithSubtype k
I find it easy to understand this distinction by writing out the types of
the constructors and case expressions for these objects, in a language like
system F:
(here, {x :: t} means a type argument with name x of kind t)
Exists :: {f :: *->*} -> {a :: *} -> f a -> Exists f
Forall :: {f :: *->*} -
The desugaring is simpler with the current setup:
do { e }
=> e
do { let p = e; STMTS }
=> let p = e in (do { STMTS })
do { e; STMTS }
=> e >> (do { STMTS })
do { p <- e; STMTS }
=> e >>= \x -> case x of { p -> (do { STMTS }) ; _ -> fail "pattern match
failure" }
[x is a fresh varia
It seems like it would still be useful for *optimizing* the implementation
of STM in Haskell; in particular, small transactions seem like a great way
to implement lock-free data structures by handling the non-composability of
compare-and-swap.
So while you wouldn't implement "atomically a" by "XBE
x27; is a left/right identity for mult':
--forall x :: m a
--mult' . O . one' . Id $ x = x = mult' . O . fmap (one' . Id)
$ x
--mult' is associative:
--forall x :: m (m (m a))).
--mult' . O . mult' . O $ x = mu
tural transformations like (\_ -> Just undefined). My guess is
that there is a side condition we can put on f that is implied by the
monoid laws which doesn't require g to be strict or total.
-- ryan
On Mon, Jan 23, 2012 at 10:23 PM, Brent Yorgey wrote:
> On Mon, Jan 23, 2012 at 09:06:5
On Mon, Jan 23, 2012 at 8:05 PM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:
> On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
> > At the end of that paste, I prove the three Haskell monad laws from the
> > functor laws and "monoid"-ish ver
I've been playing around with the relationship between monoids and monads
(see
http://www.jonmsterling.com/posts/2012-01-12-unifying-monoids-and-monads-with-polymorphic-kinds.htmland
http://blog.sigfpe.com/2008/11/from-monoids-to-monads.html), and I put
together my own implementation which I'm quit
I don't currently have anything to add to this discussion, but I want to
encourage you all to keep having it because I think it has potential to
improve the language in the "do things right or don't do them at all"
philosophy that Haskell tends towards.
-- ryan
On Fri, Jan 20, 2012 at 6:32 AM,
Has anyone played with Idris (http://idris-lang.org/) at all? It looks
interesting, and I'd love to play with it, but unfortunately I only have
windows machines up and running at the moment and the documentation seems
to imply it only builds on unixy systems.
I'm curious how difficult it would be
On Fri, Nov 18, 2011 at 4:05 AM, Yves Parès wrote:
> (Sorry for the double mail)
> ...so there is no way to do that inside the function passed to modifySTRef?
> In other words, there is no way to ensure *inside* a function that its
> result will be evaluated strictly?
modifySTRef looks like thi
If the internal vectors are fixed size, you can easily write a wrapper
around Vector Int that converts (Int,Int) indices into indices in the
sub-vector.
If the internal vectors have dynamic size, you can't declare an Unbox
instance, because pointers can't be unboxed; unboxed types are opaque to
th
First, let's lay out our definitions:
unzip [] = ([], [])
unzip ((x,y):xys) = (x:xs, y:ys) where (xs,ys) = unzip xys
zip [] _ = []
zip _ [] = []
zip (x:xs) (y:ys) = (x,y) : zip xs ys
map _ [] = []
map f (x:xs) = f x : map f xs
stream ~(a:as) = a : stream as
-- equivalently
stream xs = head xs :
Never mind, I misread the code, 'zip' and the lazy definition of stream
should add the necessary laziness.
-- ryan
On Tue, Nov 1, 2011 at 3:36 PM, Ryan Ingram wrote:
> Try
>
> swap p = (snd p, fst p)
>
> or, equivalently
>
> swap ~(x,y) = (y,x)
>
> -- r
Try
swap p = (snd p, fst p)
or, equivalently
swap ~(x,y) = (y,x)
-- ryan
On Tue, Nov 1, 2011 at 1:30 PM, Captain Freako wrote:
> Hi John,
>
> I'm trying to use the GHCI debugger on this code:
>
> 20 instance ArrowLoop SF where
> 21 loop (SF f) = SF $ \as ->
> 22 let (bs, cs)
On Mon, Oct 31, 2011 at 6:52 PM, Paterson, Ross wrote:
>
> If you require the circuit to be parametric in the value types, you can
> limit the types of function you can pass to arr to simple plumbing.
> See the netlist example at the end of my "Fun of Programming" slides (
> http://www.soi.city.ac
On Tue, Nov 1, 2011 at 3:36 AM, Serguey Zefirov wrote:
> 2011/11/1 Ryan Ingram :
> Would you mind give me some examples on how you desribe real circuits
> with that abstraction and, especially, an Arrow instance (even
> imaginary one)?
>
Sure, here's a simple SR latch:
PM, Felipe Almeida Lessa <
felipe.le...@gmail.com> wrote:
> On Mon, Oct 31, 2011 at 10:33 PM, Ryan Ingram
> wrote:
> > The arrow syntax translation uses arr to do plumbing of variables. I
> think
> > a promising project would be to figure out exactly what plumbing is
>
I know it's a bit of an 'intentionally provocative' title, but with the
recent discussions on Arrows I thought it timely to bring this up.
Most of the conversion from arrow syntax into arrows uses 'arr' to move
components around. However, arr is totally opaque to the arrow itself, and
prevents des
On Sun, Oct 30, 2011 at 8:44 AM, Anton Kholomiov
wrote:
> I'm misunderstanding astar. I've thought that 'whole route'-heuristic
> will prevent algorithm from going in circles. The more you circle around
> the more the whole route distance is.
>
Sort of. Consider the tree in my example graph:
A
On Tue, Oct 25, 2011 at 1:46 PM, Ben Franksen wrote:
> > IME, there are (at least) two possible problems
> > here, 1) transactions scale (quadratically, I think) with the number of
> > TVars touched,
>
> Ouch! What would be the reason for that? I thought it would be linear... I
> mean what happens
Also, this wasn't clear in my message, but the edges in the graph only go
one way; towards the top/right; otherwise the best path is ABCDEHIJ :)
On Thu, Oct 27, 2011 at 10:48 AM, Ryan Ingram wrote:
> You're missing one of the key insights from A-star (and simple djikstra,
>
You're missing one of the key insights from A-star (and simple djikstra, for
that matter): once you visit a node, you don't have to visit it again.
Consider a 5x2 2d graph with these edge costs:
B 1 C 1 D 1 E 9 J
1 1 1 1 1
A 2 F 2 G 2 H 2 I
with the start node being A, the target node be
Your type stopped being an arrow when the state type started to depend on
the input type:
Filter a b ~= (a, FS a) -> (b, FS a)
Filter b c ~= (b, FS b) -> (c, FS b)
It's impossible to compose these two functions into a single function of
type Filter a c, because the state type doesn't match.
You
On Sun, Oct 9, 2011 at 6:18 AM, Ryan Newton wrote:
>
> Yep, it is simple. But I prefer to only use well-tested data structure
> libraries where I can! Here's an example simple implementation (partial --
> missing some common functions):
>
>
> module Data.BitList
> ( BitList
> , cons, head,
Your filter type isn't a Monad.
In particular
bind :: (a -> EitherT e (State FilterState) a) -> (a -> b -> EitherT e
(State FilterState) b) -> b -> EitherT e (State FilterState) b
can't be implemented, as you have no place to grab an 'a' to pass to the
initial computation.
If you fix the input
You can use Data.Sequence.fromList to go [a] -> Seq a, though.
So given
f :: Monad m => a -> m b
you have
import Data.Traversable as T
import Data.Sequence as S
g :: Monad m => [a] -> m (S.Seq b)
g = T.mapM f . S.fromList
- ryan
On Wed, Sep 28, 2011 at 6:20 PM, Marc Ziegert wrote:
> Hi T
tried specializations, then I removed a lot of polimorphism,
> but nothing helped, it was like hitting a wall.)
>
> Even more amazingly is that I could program it although I cannot really
> understand the Cont & ContT, but just taking the code example from Ryan
> Ingram (newtype Con
The other option is
{-# LANGUAGE ExistentialQuantification #-}
data Renderer s = Renderer {
initialize :: IO s,
destroy :: IO (),
renderS :: SystemOutput -> s -> IO s
}
-- Now, you need to hold the state somewhere, which you can do with an
existential:
data InitializedRenderer = fo
On Tue, Aug 30, 2011 at 4:53 PM, Sebastian Fischer wrote:
> I think the idea of functional lists is that the monoids of 'lists'
> and 'functions on lists' are isomorphic with isomorphisms toFList and
> toList:
>
>toFList [] = id
>toFList (xs++ys) = toFList xs . toFList ys
>
>toList id
On Tue, Aug 30, 2011 at 9:42 AM, Conal Elliott wrote:
> I suspect this definition is what Sebastian meant by "converting back and
forth to ordinary lists".
Yep, I know; and technically it violates 'fmap id' == 'id'
for example,
fmap id (FList $ \xs -> xs ++ xs) = FList $ \xs -> xs
If you add th
The problem with hiding the context in the constructor is that there's no
guarantee that the context actually exists in the first place; for example,
given this type
data IsInt a where
Proof :: IsInt Int
this is a legal program:
foo :: IsInt Bool
foo = undefined
That said, you are still jus
On Sun, Aug 28, 2011 at 8:24 PM, Maciej Marcin Piechotka <
uzytkown...@gmail.com> wrote:
> f `fmap` FList g = _|_
> f `fmap` FList g = map id
> f `fmap` FList g = map _|_
> (+ variation of _|_*)
>
f `fmap` FList g = \bs -> map f (g []) ++ bs
___
Haskell
On Wed, Aug 17, 2011 at 4:49 PM, Tom Schouten wrote:
> {-# LANGUAGE ExistentialQuantification #-}
>
> -- Dear Cafe, this one works.
> data Kl' s i o = Kl' (i -> s -> (s, o))
> iso' :: (i -> Kl' s () o) -> Kl' s i o
> iso' f = Kl' $ \i s -> (\(Kl' kl') -> kl' () s) (f i)
>
> -- Is there a way to m
On Tue, Aug 2, 2011 at 5:57 AM, Patrick Browne wrote:
> data Eq a => Set1 a = NilSet1 | ConsSet1 a (Set1 a)
> data Set2 a = NilSet2 | ConsSet2 a (Set2 a) deriving Eq
>
The former declaration is a language wart, IMO. All it does is attach a
restriction to the constructors of Set1; try
>
Use memoization. Here's an example:
cabal-install MemoTrie
import Data.MemoTrie
fib_fix :: (Integer -> Integer) -> Integer -> Integer
fib_fix _ n | n < 0 = error "invalid input"
fib_fix _ 0 = 1
fib_fix _ 1 = 1
fib_fix rec n = rec (n-1) + rec (n-2)
-- 'tie the knot' on a recusrive function
fun
My guess is that nobody has put forward a clear enough design that solves
all the problems. In particular, orphan instances are tricky.
Here's an example:
module Prelude where
class (Functor m, Applicative m) => Monad m where
return :: a -> m a
(>>=) :: m a -> (a -> m b) -> m b
(>>)
On Thu, Jul 7, 2011 at 11:08 PM, Heinrich Apfelmus <
apfel...@quantentunnel.de> wrote:
> Do you know any *small GUI programs* that you would *like* to see
> *implemented with Functional Reactive Programming?*
>
I think this is an admirable effort. My suggestions are 'Stuff that came
with Windows
On Sun, Jul 3, 2011 at 2:05 AM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:
> But as I understand it, the concern is ghci, where truly local bindings are
> probably rare and type signatures are commonly omitted.
> So putting ":s -XNoMonomorphismRestriction" in the .ghci file probably
Figuring out how to tell what type ghci is defaulting to was an interesting
exercise. The sum [] trick seemed cool, so I tried a variant:
Prelude> let f xs = const xs $ show xs
Prelude> f []
[]
Prelude> :t it
it :: [()]
-- ryan
On Thu, Jun 30, 2011 at 6:44 PM, Ivan Lazar Miljenovic <
ivan.mi
So this is definitely a GHC bug, but I think the problem is probably
triggered by this line:
instance Serializable a b => IResource a
I don't think this is a valid instance declaration without a functional
dependency on Serializable, as it's impossible to know which type 'b' to use
in the method
I always forget to reply all. Silly gmail.
On Mon, Jun 6, 2011 at 2:07 AM, Ryan Ingram wrote:
> Hi Pat. There aren't any casts in that code. There are type annotations,
> but this is different than the idea of a cast like in C.
>
> For example
> ((3 :: Integer) ::
On Tue, May 31, 2011 at 1:40 AM, Patrick Browne wrote:
> Continuing the thread on model expansion.
> I have changed the example trying to focus on expanding models of M in G
> Why is the operation ! ok or RHS but not visible on LHS of G?
> The equation itself does not seem to suffer from the depen
I suggest you take a look at MonadPrompt and/or Operational (two competing
packages, one of which I wrote).
And yes, you probably need some operation
Concurrent :: [Mission ()] -> Mission ()
or
Interrupt :: Mission () -> Mission Bool -> Mission () -> Mission ()
which runs its first argument unti
Hi Patrick.
What you are doing isn't possible in source code (Haskell doesn't prove
things at the value level like a dependently typed language does.)
Usually you document it just as you have, as a comment
-- inverse a ! a = e
You can also specify a QuickCheck property:
propInverse :: (Eq
Think of it this way:
-- Here is some data representing the typeclass 'Show'
data ShowDict a = ShowD (a -> String)
show :: ShowDict a -> a -> String
show (ShowD f) a = f a
-- Here's a sample implementation for Strings
showString :: ShowDict String
showString = ShowD (\s -> "\"" ++ escape s ++ "\"
Yes, the goal isn't so much to improve complexity (both are O(1)) but to
reduce the constant factor on that O(1).
In an inner loop like that, allocator/gc calls by far dominate the cost of
the program. If you can remove them, you've improved the performance of the
program by 10-100x.
In the case
The behavior you are asking for "maybeShow" violates parametricity, so it
can't exist without some sort of typeclass constraint.
That said, in your particular situation, it's an interesting question.
The Show instance for Either is
instance (Show a, Show b) => Show (Either a b) where ...
so we
On Tue, Apr 26, 2011 at 11:44 PM, Heinrich Apfelmus <
apfel...@quantentunnel.de> wrote:
> However, even in a demand-driven implementation, there is one optimization
> that I would like make: when there are multiple external events, say e1 and
> e2, the network splits into subnetworks that react on
Apfelmus, I hope you don't abandon your efforts, at least for the selfish
reason that I enjoy reading your blog entries about trying to implement it!
I was looking at your last entry and trying to understand if/how you solve
the order-dependency problem for events. In particular:
source events e
Mail fail, haha. Code fixed.
For example:
-- Library functions for a hypothetical FRP system
pollEvent :: IO [a] -> Event a
behavior :: a -> Event a -> Behavior a
accumB :: b -> (b -> a -> b) -> Event a -> Behavior b
accumE :: b -> (b -> a -> b) -> Event a -> Event b
union :: Event a -> Event a -
Of course, you could have the 'interpretation' function be non-pure.
For example:
-- Library functions for a hypothetical FRP system
pollEvent :: IO [a] -> Event a
behavior :: a -> Event a -> Behavior a
accumB :: b -> (b -> a -> b) -> Event a -> Behavior b
accumE :: b -> (b -> a -> b) -> Event a
I've been working on Haskell for quite a while and it's not too often that a
beginner shows me a new trick--this trick with trace seems really cool and I
hadn't seen it before.
f x | trace ("f " ++ show x) False = undefined
f ... -- rest of regular definition
Makes it really easy to add the trace
So if we were to emulate your Java solution, we'd do
import Data.Array
cacheSize :: Int
cacheSize = 65536
table :: Array Int Integer
table = listArray (1,cacheSize) (1 : map go [2..cacheSize]) where
go n
| even n = 1 + lookup (n `div` 2)
| otherwise = 1 + lookup (3 * n + 1)
On Sun, Apr 3, 2011 at 1:00 PM, Tad Doxsee wrote:
> "Equality constraints ... enable a simple translation of programs
>using functional dependencies into programs using family
>synonyms instead.
>
> So I tried:
>
> class (T s ~ a) => ShapeC a s where
> type T s :: *
> draw :: s -> Str
On Thu, Mar 31, 2011 at 7:29 AM, Daniel Fischer <
daniel.is.fisc...@googlemail.com> wrote:
> Err, terminology problem here.
> Strictly speaking, a function is strict iff
>
> f _|_ = _|_
>
> while we are talking here about evaluation strategies, so we should better
> have spoken of eager vs. deferr
On Fri, Mar 4, 2011 at 3:45 PM, Yves Parès wrote:
> Hello,
>
> For testing purposes, I am trying to make an overlay to IO which carries a
> phantom type to ensure a context.
> I define contexts using empty type classes :
>
> class CtxFoo c
> class CtxBar c
>
> The overlay :
>
> newtype MyIO c a =
You might want to take a look at
http://hackage.haskell.org/package/Adaptivesince it seems really
similar to what you are trying to do. In fact, you
might also want to google 'Functional Reactive Programming'.
-- ryan
On Thu, Feb 24, 2011 at 10:41 PM, Chris Dew wrote:
> Hello, just like ever
Just write a loop:
> let loop gs gu
>| Just z <- find_obj gu usyms = do
>...
>(gs', gu') <- handle_obj_ar ...
>loop gs' gu'
>| otherwise = return (gs,gu)
> (gs, gu) <- loop def undef
mfix is for when you have mutually recursive data but you want the IO
One way to think about Reactive's notion of "Future" is as a single
element of an event stream--something that might happen (yielding a
value) some time in the future.
'mempty' on futures is a future that never happens, and 'mappend' says
to pick the first of two futures to happen.
m >>= k waits f
Hi Sam. I don't know much about the performance problems you are
seeing, but I think your solution is more cleanly implemented just
under the event level with futures.
I think the reactive function you want has a type like this:
stateMachine :: s -> (a -> s -> s) -> (s -> Future (b, s)) -> Event
Can you just wrap it? Something like this:
-- put your monad type here
type M a = Iteratee ... a
data W a = W (Iteratee ... a) deriving Typeable
unW (W x) = x
toDynW :: Typeable a => M a -> Dynamic
toDynW x = toDynamic (W x)
castM :: (Typeable x, Typeable a) => x -> Maybe (M a)
castM = unW . c
On Fri, Jan 21, 2011 at 7:58 PM, Casey Hawthorne wrote:
> uj supplied this:
>
> About the discussion
> "putStrLn (readLn + (5 :: Int))"..
>
> I'll write it as the following line,
>
> importing Control.Applicative
> main = (+) readLn (return 3)
>
> They look almost exactly same in my eyes..
You're
Interesting little paper, Tyson.
You bring up other programming languages and 'ad-hoc systems for
resolving ambiguities'; I agree with you that these systems generally
have no strong theoretical basis, but I'm not sure that's a terribly
bad thing.
I think what a programmer actually wants from amb
On Wed, Jan 19, 2011 at 11:56 PM, Patrick Browne wrote:
> I am trying to see what how this requirement can be represented using
> just the normal instance-implements-class relation for a comparison with
> a specification language approach.
>
> If there is no simple way to do this using type classe
1 - 100 of 721 matches
Mail list logo