Re: [Haskell-cafe] Painful Data Abstraction

2009-04-07 Thread Ryan Ingram
On Tue, Apr 7, 2009 at 6:11 PM, Brad Larsen wrote: >   prop_insert_idempotent :: (Eq d, PrefixDict d) => d -> Word -> Bool >   prop_insert_idempotent d w = insert w d' == d' >     where d' = insert w d > > The problem is this:  I can't think of a non-kludged way of checking that > TrieDict and Lis

Re: [Haskell-cafe] Strange type error with associated type synonyms

2009-04-06 Thread Ryan Ingram
On Mon, Apr 6, 2009 at 2:36 PM, Peter Berry wrote: > As I understand it, the type checker's thought process should be along > these lines: > > 1) the type signature dictates that x has type Memo d a. > 2) appl has type Memo d1 a -> d1 -> a for some d1. > 3) we apply appl to x, so Memo d1 a = Memo

Re: [Haskell-cafe] Infix tuple comma query (,)

2009-04-06 Thread Ryan Ingram
The prefix notation for > \a b c -> (a,b,c) is (,,) Without the parentheses, it's not immediately clear whether > foo $ a,b means > foo (a,b) or > foo (\c -> (a,b,c)) or some other, bigger tuple size. Anyways, it's just syntax :) -- ryan On Mon, Apr 6, 2009 at 9:08 AM, Daniel Fischer wrote:

Re: [Haskell-cafe] Re: Looking for practical examples of Zippers

2009-03-31 Thread Ryan Ingram
ourse that this use is feasible at all. > > Hi Günther, > > a couple of weeks ago I was looking into Zippers my self as well. > After reading all the documents mentioned in the other messages, I > decided to go for my implementation as the proposed ones seemed to me > unnecessarily compli

Re: [Haskell-cafe] Rational and % operator remix

2009-03-30 Thread Ryan Ingram
2009/3/30 michael rice : > I'm still not sure what some of the error messages I was getting were about. > As I wrote the function I tried to be aware of what "mixed mode" operations > were kosher ala This is a mistake, but understandable given your lispy background; there aren't really "mixed mode

Re: [Haskell-cafe] Record updates

2009-03-29 Thread Ryan Ingram
Take a look at Data.Accessor on hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template -- ryan On Sun, Mar 29, 2009 at 2:13 AM, Andrew Coppin wrote: > Haskell's record syntax is quite

Re: [Haskell-cafe] type Rational and the % operator

2009-03-28 Thread Ryan Ingram
Just use "/" for division. % is for construction of rationals from the "underlying" numeric type. For example, instead of "toRational x" you can write "x % 1". -- ryan 2009/3/28 michael rice : > I may be missing something here, but this is what I intended. > > An expression of the form > >  

Re: [Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-25 Thread Ryan Ingram
On Wed, Mar 25, 2009 at 8:25 AM, Jonathan Cast wrote: > On Wed, 2009-03-25 at 15:09 +, Simon Marlow wrote: >> the ordering that the state monad expects >> (and I can never remember which way around they are in Control.Monad.State). > > Really?  I found it obvious once I figured out it how simp

Re: [Haskell-cafe] about beta NF in lambda calculus

2009-03-21 Thread Ryan Ingram
Given the Y combinator, Y (\x.x) has no normal form. However, (\a. (\x. x)) (Y (\x. x)) does have a normal form; (\x. x). But it only reduces to that normal form if you reduce the (\a. ...) redex, not if you reduce its argument. So depending on evaluation order you might not reach a normal form.

Re: [Haskell-cafe] least fixed points above something

2009-03-20 Thread Ryan Ingram
On Fri, Mar 20, 2009 at 1:01 AM, Dan Doel wrote: > However, to answer Luke's wonder, I don't think fixAbove always finds fixed > points, even when its preconditions are met. Consider: > >  f []     = [] >  f (x:xs) = x:x:xs > >  twos = 2:twos How about > fixAbove f x = x `lub` fixAbove f (f x)

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Ryan Ingram
On Wed, Mar 18, 2009 at 8:10 AM, David Menendez wrote: > l_out :: Functor f => Lfix f -> f (Lfix f) > l_out = cata (fmap l_in) > > g_in :: Functor f => f (Gfix f) -> Gfix f > g_in = ana (fmap g_out) OK, I understand these now. But they both seem to have significant performance implications, whic

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Ryan Ingram
On Wed, Mar 18, 2009 at 8:10 AM, David Menendez wrote: > l_out :: Functor f => Lfix f -> f (Lfix f) > l_out = cata (fmap l_in) > > g_in :: Functor f => f (Gfix f) -> Gfix f > g_in = ana (fmap g_out) Well, you just blew my mind. I had an informal proof in my head of why g_in shouldn't be possible

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Ryan Ingram
One typo correction: On Wed, Mar 18, 2009 at 2:15 AM, Ryan Ingram wrote: > Let "Pair a b" be an abbreviation for "forall c. (a -> b -> c)", This should say that Pair a b is an abbreviation for forall c. (a -> b -> c) -> c -- ryan _

Re: [Haskell-cafe] encoding for least fixpoint

2009-03-18 Thread Ryan Ingram
On Tue, Mar 17, 2009 at 4:36 PM, ben wrote: > Then I stumbled over a blog entry of Shin-Cheng Mu [2] and from there > over an article of Wadler [3], where the least fixpoint is encoded as > > Lfix X. F X  =  All X. (F X -> X) -> X. > > and the greatest fixpoint as > > Gfix X. F X  =  Exists X. (X

Re: [Haskell-cafe] Type equality proof

2009-03-17 Thread Ryan Ingram
On Tue, Mar 17, 2009 at 10:30 AM, Brent Yorgey wrote: > I don't understand your classes Eq1, Eq2, and Eq3.  How would you make > an instance of Eq1 for, say, [] ? You don't. > It seems you are confusing _value_ equality with _type_ equality?  A > value of type a :=: a' is a proof that a and a' a

Re: [Haskell-cafe] using Typeable with STRefs

2009-03-16 Thread Ryan Ingram
Having the state be an instance of Typeable breaks the purity guarantees of runST; a reference could escape runST: let v = runST (V `liftM` newSTRef 0) in runST (readSTRef $ fromJust $ getValue v) Keep in mind that the state actually used by runST is "RealWorld"; runST is just a pretty name f

Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-16 Thread Ryan Ingram
On Mon, Mar 16, 2009 at 7:55 AM, Jake McArthur wrote: > I think it depends on what we want to take "unsafe" to mean. In my > opinion, the word "unsafe" should really only be used in cases where > using the function can case an otherwise well-typed program to not be > well-typed. I'm pretty sure I

Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Ryan Ingram
On Sun, Mar 15, 2009 at 1:56 PM, Jonathan Cast wrote: >> But not if you switch the (x <- ...) and (y <- ...) parts: >> >> main = do >>     r <- newIORef 0 >>     v <- unsafeInterleaveIO $ do >>         writeIORef r 1 >>         return 1 >>     y <- readIORef r >>     x <- case f v of >>          

Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Ryan Ingram
unsafeInterleaveIO allows embedding side effects into a pure computation. This means you can potentially observe if some pure value has been evaluated or not; the result of your code could change depending how lazy/strict it is, which is very hard to predict! For example: > -- given > f :: Inte

Re: [Haskell-cafe] Hashing over equivalence classes

2009-03-14 Thread Ryan Ingram
For the second case you might be able to come up with a commutative hash-combiner function for && and ||. For the lambda-term situation, I can think of a couple ways to hash that give what you want. (1) Ignore variable names altogether while hashing; this gives you what you want but has the disad

Re: [Haskell-cafe] Hand calculation of Bird's definition of zip using foldr

2009-03-12 Thread Ryan Ingram
2009/3/12 R J : > Part of my problem is that "e" is defined as a function that takes > one argument, I don't see how that fits in with the usual scheme for foldr, > which, as I understand it, is: > > foldr f e [x1, x2, ...] = f x1 (f x2 (f x3 ...(f xn e)))... It's pretty easy, actually. Lets rewr

Re: [Haskell-cafe] A systematic method for deriving a defintion of foldl using foldr?

2009-03-11 Thread Ryan Ingram
2009/3/11 R J : > 3.  Any advice on how, aside from tons of practice, to develop the intuition > for rapidly seeing solutions to questions like these would be much > appreciated.  The difficulty a newbie faces in answering seemingly simple > questions like these is quite discouraging. Don't be dis

Re: [Haskell-cafe] I want to write a compiler

2009-03-08 Thread Ryan Ingram
I really like this book: http://research.microsoft.com/en-us/um/people/simonpj/papers/pj-lester-book/ It walks you through building a compiler to a reasonable intermediate language, which you can then start with; it's is a much easier problem to convert that intermediate langauge to assembly, C,

Re: [Haskell-cafe] Hint and Ambiguous Type issue

2009-03-05 Thread Ryan Ingram
So, by using the Haskell interpreter, you're using the not-very-well-supported dynamically-typed subset of Haskell. You can tell this from the type signature of "interpret": > interpret :: Typeable a => String -> a -> Interpreter a > as :: Typeable a => a > as = undefined (from http://hackage.

Re: [Haskell-cafe] Re: Zippers

2009-03-04 Thread Ryan Ingram
On Wed, Mar 4, 2009 at 12:53 PM, Cristiano Paris wrote: > I'd (and indeed I did) write 'update' as: > > update z x = z { this = this z >> Just x } > > exploiting the '>>' operator's logic. How would this differ from the > corresponding 'update' in the original Huet's FP? Maybe I don't get > how my

Re: [Haskell-cafe] Interesting problem from Bird (4.2.13)

2009-03-04 Thread Ryan Ingram
2009/3/4 R J : > What's the pure solution that uses cases and recursion on > CatList, not Haskell's built-in lists, to capture the equality of nested > CatLists? As Rafael pointed out, the simplest thing to do is to convert to a canonical form; you can prove that each CatList has a single canonica

Re: [Haskell-cafe] Memory usage when passing arrays in state

2009-03-03 Thread Ryan Ingram
I've found DiffArrays to be way too slow/memory-hogging for real usage. Since you are in IO already (StateT s IO), you'll probably be better off using a mutable array for a data structure. Some things are still best done in the imperative style. You can be a bit safer by using ST as the bottom m

Re: [Haskell-cafe] Re: ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-27 Thread Ryan Ingram
:27 PM, David Menendez wrote: > On Fri, Feb 27, 2009 at 1:28 PM, Ryan Ingram wrote: >> Then it comes down to, within a session, is there some way for an >> STTRef to "mingle" and break the type-safety rule.  I can think of two >> potential ways this might happen.  First

Re: [Haskell-cafe] Re: ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-27 Thread Ryan Ingram
something like Cont, there may be a way for an STTRef to get transmitted "back in time" via a continuation to a point where it hadn't been allocated yet. So if there is a counterexample I expect it to come down to one of those two cases. -- ryan On Thu, Feb 26, 2009 at 11:22

Re: [Haskell-cafe] Help with Bird problem 3.3.3

2009-02-24 Thread Ryan Ingram
Try starting with (m * n) / m = n -- given m /= 0 Then do case analysis on n. I found this process quite enlightening, thanks for posting. -- ryan 2009/2/24 Peter Hilal : > I'm working my way through Bird's _Introduction to Functional Programming > Using Haskell_. I'd appreciate any help

Re: [Haskell-cafe] forall & ST monad

2009-02-23 Thread Ryan Ingram
On Fri, Feb 20, 2009 at 11:33 AM, Kim-Ee Yeoh wrote: > Here's a counterexample, regardless of whether you're using > constructive or classical logic, that (forall a. T[a]) -> T' does > not imply exists a. (T[a] -> T'). > > Let a not exist, but T' true. Done. That isn't quite a proper counterexamp

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-20 Thread Ryan Ingram
- but I suppose that since mutable >> references are really equivalent to single-threadedness where referential >> transparency is concerned, that could be pulled off -- I would still want a >> StateThread associated type, but that'd just be RealWorld for IO and STM, I >> gu

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-19 Thread Ryan Ingram
So, why not use this definition? Is there something special about ST you are trying to preserve? -- minimal complete definition: -- Ref, newRef, and either modifyRef or both readRef and writeRef. class Monad m => MonadRef m where type Ref m :: * -> * newRef :: a -> m (Ref m a) readRef

Re: [Haskell-cafe] question on types

2009-02-18 Thread Ryan Ingram
On Wed, Feb 18, 2009 at 2:12 AM, Lennart Augustsson wrote: > Also, if you are using ghc you can turn on the extension that allows > undecidable instances and make the type system Turing complete. And you get the additional pain of a potentially nonterminating compiler without any of the nice type

Re: [Haskell-cafe] Re: forall & ST monad

2009-02-17 Thread Ryan Ingram
On Tue, Feb 17, 2009 at 5:22 AM, Dan Doel wrote: > -- fail: inferred type less polymorphic than expected > -- This seems like it could perhaps work, since E'' > -- re-hides the 'a' but it doesn't, probably because there's > -- no way to type the enclosed lambda expression properly. > -- You'd prob

Re: [Haskell-cafe] Re: Low-level high-level languages?

2009-02-16 Thread Ryan Ingram
C-- is kind of dead; it lives on in spirit as a data type used by the back end of GHC, but there hasn't been much development in C-- as a language proper in a while. LLVM seems to be gaining momentum in that space; Lennart has been posting some experiments with generating LLVM code in Haskell in h

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-16 Thread Ryan Ingram
Don't use the > data (context) => type = constructors syntax, it doesn't do what you want. All it does is add the context to the constructor B while not providing it to any of the functions that use it. A better solution is > data Bar a = forall b. Foo a b => B a b or, equivalently, using GADT

Re: [Haskell-cafe] ANNOUNCE: pqueue-mtl, stateful-mtl

2009-02-15 Thread Ryan Ingram
You can roll your own pure STT monad, at the cost of performance: -- Do not export any of these constructors, just the types STT and STTRef. data W = forall a. W !a data Heap s = Heap !Int !(IntMap W) newtype STT s m a = STT (StateT (Heap s) m a) deriving (Monad, MonadTrans, MonadIO, insert other

Re: [Haskell-cafe] forall & ST monad

2009-02-15 Thread Ryan Ingram
On Sun, Feb 15, 2009 at 11:50 AM, Kim-Ee Yeoh wrote: > Having said that, I'm not sure about the statement on page 9 > that "readVar v simply does not have type forall s. ST s Bool." > The variable v could be of type "forall s. MutVar s Bool", > in which case all of "runST (readVar v)" typechecks.

Re: [Haskell-cafe] Possible bug?

2009-02-14 Thread Ryan Ingram
2009/2/13 Peter Verswyvelen : > No the error I got was > Could not deduce (Controller m v c) > from the context (Controller m v c2) > arising from a use of `MVC' at NM8\GUI\PanZoom.hs:126:32-65 > Possible fix: > add (Controller m v c) to the context of the constructor `MVC' > In

Re: [Haskell-cafe] can't figure out a type

2009-02-11 Thread Ryan Ingram
You can do this with another type class. class (Chunkable c1 el1, Chunkable c2 el2) => ChunkMap c1 el1 c2 el2 where cMap :: (el1 -> el2) -> c1 -> c2 instance ChunkMap [a] a [b] b where cMap = map If you want to assert that c1 and c2 are really related, you can add functional dependencies to

[Haskell-cafe] Re: type metaphysics

2009-02-02 Thread Ryan Ingram
On Mon, Feb 2, 2009 at 3:55 PM, Benedikt Huber wrote: > f is 'easy to implement' if it enumerates all functions, not just total > ones. Otherwise, f is hard to implement ;) > > In the first case, if we have (f n n) = _|_, then g n = not (f n n) = _|_ as > well, so the diagonalization argument does

Re: [Haskell-cafe] type metaphysics

2009-02-02 Thread Ryan Ingram
2009/2/2 Luke Palmer : > However! If we have a function f : Nat -> Nat -> Bool, we can construct the > diagonalization g : Nat -> Bool as: g n = not (f n n), with g not in the > range of f. That makes Nat -> Bool "computably uncountable". This is making my head explode. How is g not in the ran

Re: [Haskell-cafe] what does "atomically#" mean?

2009-01-31 Thread Ryan Ingram
That code is in /rts/STM.c -- ryan 2009/1/30 Daryoush Mehrtash : > I like to look at the code where the runtime detects a TVar, inside an > atomic block, has been changed by another thread and hence it aborts the > atomic operation. Any suggestion as to where I would find the code? > > daryou

Re: Re[Haskell-cafe] cursive referencing

2009-01-31 Thread Ryan Ingram
1) yes, but that's sumAA's fault, not the data structure; sumAA isn't tail recursive so it has to build a much bigger stack: x + (y + (z + (...))) whereas it could run in constant space if it did this instead: (...((x + y) + z) + ...) Usually this transformation is done by passing an accumulato

Re: Re[Haskell-cafe] cursive referencing

2009-01-29 Thread Ryan Ingram
On Thu, Jan 29, 2009 at 12:44 AM, Eugene Kirpichov wrote: > With the Y combinator, the code becomes as follows: > > f = \somedata1 somedata2 -> fst $ fix (\(aa,bb) -> (AA somedata1 bb, > BB somedata2 aa)) > > I tried to prove to myself that the structure really turns out cyclic, > but games with r

Re: [Haskell-cafe] Gentle introduction questions / comments

2009-01-27 Thread Ryan Ingram
2009/1/27 Matthijs Kooijman : > Hi all, > > I've been reading the gentle introduction to Haskell a bit more closely today > and there a few things which I can't quite understand (presumably because they > are typo's). I've found two issues with the "Using monads" section [1]. Not > sure if this is

Re: [Haskell-cafe] Fold that quits early?

2009-01-24 Thread Ryan Ingram
flaw in your logic, but it's > not true of my usage. Your definition always produces a non-null list. The > particular g in my mind will eventually produce a null list, somewhere down > the line. I think if that's true, we can guarantee termination. > > On Sat, Jan 24, 200

Re: [Haskell-cafe] Fold that quits early?

2009-01-24 Thread Ryan Ingram
foldr f z xs = x0 `f` (x1 `f` (x2 `f` ... (xN `f` z) ...)) In particular, note that if f is a total function, xs is finite and totally defined, and z is totally defined, then the result of this fold is totally defined. Now consider your "f" (rewritten slightly) f x xs | null xs = [] | p

Re: [Haskell-cafe] How to define an operation in terms of itself (but of different type)?

2009-01-24 Thread Ryan Ingram
2009/1/24 Olex P : > What I want to ask you guys can we define a function with arbitrary number > of parameters? Actually not really arbitrary but just several possibilities > (as we have with value constructors). > For instance cross product can have 1, 2 or 3 vectors as inputs depends on > the di

Re: Laws and partial values (was: [Haskell-cafe] mapM_ -> Monoid.Monad.map)

2009-01-24 Thread Ryan Ingram
On Fri, Jan 23, 2009 at 10:49 PM, Thomas Davie wrote: > Isn't the point of bottom that it's the least defined value. Someone above > made the assertion that for left identity to hold, _|_ `mappend` () must be > _|_. But, as there is only one value in the Unit type, all values we have > no inform

Re: [Haskell-cafe] Current research on overlapping/closed type families?

2009-01-23 Thread Ryan Ingram
oundness. > > But we have not yet implemented the idea yet. First priority is to get type > families working properly, and in conjunction with type classes. Then we can > move on to adding features. > > Simon > > | -Original Message- > | From: haskell-cafe-bou

Re: [Haskell-cafe] Applicative/Monad for Either

2009-01-21 Thread Ryan Ingram
I think it's possible, but not in a very clean way. First lets look at ap: > ap mf mx = do > f <- mf > x <- mx > return (f x) equivalently, desugared: > ap mf mx = mf >>= \f -> mx >>= \x -> return (f x) So, it's possible to make a definition of >>= where "ap" works as you like: >Z (

Re: [Haskell-cafe] Elevator pitch for functional programming

2009-01-20 Thread Ryan Ingram
I recommend checking out Don Syme's slides from CUFP 2008. http://cufp.galois.com/2008/slides/ This isn't Haskell directly, it's F#, but it fits the "functional programming generally", and the two languages have, relative to the universe of programming languages, more in common than they do diffe

[Haskell-cafe] Current research on overlapping/closed type families?

2009-01-19 Thread Ryan Ingram
What's the status of overlapping/closed type families? I'm interested in something like the following, which can currently be implemented in GHC with Oleg-magic using functional dependencies, but cannot, to my knowledge, be implemented with type families: data HTrue = HTrue data HFalse = HFalse

Re: [Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread Ryan Ingram
ilator op ann x y = > assuming (x == ann) ann `unamb` > assuming (y == ann) ann `unamb` > (x `op` y) > > [1] http://haskell.org/haskellwiki/Unamb > [2] > http://hackage.haskell.org/packages/archive/unamb/latest/doc/html/Data-Unamb.html > [3] http://conal.

Re: [Haskell-cafe] Re: How to make code least strict?

2009-01-19 Thread Ryan Ingram
On Mon, Jan 19, 2009 at 9:10 AM, ChrisK wrote: > Consider that the order of pattern matching can matter as well, the simplest > common case being zip: > > zip xs [] = [] > zip [] ys = [] > zip (x:xs) (y:ys) = (x,y) : zip xs ys If you are obsessive about least-strictness and performance isn't a gi

Re: [Haskell-cafe] Stupid question, re: overloaded type classes

2009-01-18 Thread Ryan Ingram
On Sun, Jan 18, 2009 at 12:43 PM, sam lee wrote: > The following code compiles fine on my ghci This seems like a bug, you didn't enable overlapping instances and these two instances clearly overlap: >instance Sexpable String where >instance Sexpable a => Sexpable [ a ] where since Strin

Re: [Haskell-cafe] Stupid question, re: overloaded type classes

2009-01-18 Thread Ryan Ingram
On Sun, Jan 18, 2009 at 11:23 AM, Brian Hurt wrote: > instance Sexpable String where > instance Sexpable a => Sexpable [ a ] where > Note that I am not implementing Sexpable Char anywhere, so the only valid > transform for [Char] should be the String one. But this still causes a > compiler erro

Re: [Haskell-cafe] Functors [Comments from OCaml Hacker Brian Hurt]

2009-01-18 Thread Ryan Ingram
On Sun, Jan 18, 2009 at 3:23 AM, Andrew Coppin wrote: > Given that liftM exists, why is having an identical implementation for fmap > useful? For many structures, it's easier to define (>>=) in terms of fmap and join. For these objects, often the "generic" implementation of liftM is far less eff

Re: [Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Ryan Ingram
Here's the desugaring: > do { pattern <- expression ; rest } desugars to > expression >>= \temp -> case temp of >pattern -> do { rest } >_ -> fail "Pattern match failure" (where "temp" is a fresh variable not used elsewhere, and the failure message usually includes source position) Whe

Re: [Haskell-cafe] How to simplify this code?

2009-01-15 Thread Ryan Ingram
Here's a series of refactorings that I feel gets to the essence of the code. For reference, here's the original. > add :: JSON a => MyData -> String -> a -> MyData > add m k v = fromJust $ (return $ json m) >>= jsObj >>= (return . > fromJSObject) >>= (return . ((k, showJSON v):)) >>= (return . >

Re: [Haskell-cafe] Re: Type errors, would extensions help?

2009-01-15 Thread Ryan Ingram
I suggest you start using "let" in your do blocks; both of these problems are solvable with let. Binding with <- instead of "let" makes the type system work harder, and will generally require type annotations & extensions for polymorphic results. And it's almost never what you want, anyways; you

Re: [Haskell-cafe] Adding Authentication and Authorization to a service implemented in Haskell

2009-01-13 Thread Ryan Ingram
At ICFP this year there was a fun presentation about this subject. The paper & library are available from: http://www.cs.chalmers.se/~russo/seclib.htm -- ryan 2009/1/13 Daryoush Mehrtash : > I am trying to figure out a clean way to add authentication and > authorization in a webservice. The

Re: [Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Ryan Ingram
> -- I'm not entirely sure on this one, because type witnesses confuse me. > compare_changes_with_old :: (Patchy p) => > FL p C(x y) > -> FL p C(x y) > -> (FL p :> FL p) C(x y) > > C(args...) is a preprocessor macro that expands to args if Darcs is >

Re: [Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Ryan Ingram
Some questions first: What's the type of this function supposed to be? What's the type of unsafeCompare? How is the data type with NilFL and :>: defined? -- ryan On Mon, Jan 12, 2009 at 5:43 AM, Rob Hoelz wrote: > Forwarding to Haskell Cafe per Eric's suggestion. > > Begin forwarded message: >

Re: [Haskell-cafe] Understanding type synonym families

2009-01-11 Thread Ryan Ingram
>From your blog post: > Another solution is to use type synonyms to flip the parameter order > around and write > > > type StateT' m s a = StateT s m a > > That in combination with the TypeSynonymInstances extension would > allow us to write instance MonadState (StateT' m), This isn't true, actual

Re: [Haskell-cafe] Declaring each instance of a typeclass to be also an instance of another typeclass

2009-01-11 Thread Ryan Ingram
No, but you can do this: > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > import Control.Monad (liftM) > newtype Functorize m a = F { unF :: m a } deriving (Eq, Show, Monad) Insert any other type classes you care about potentially inheriting from the parent Monad into the deriving clause, like Mo

Re: [Haskell-cafe] Propositional logic implementation

2009-01-10 Thread Ryan Ingram
I like using smart constructors to replace :<=>: and :=>: a \/ b = a :\/: b a /\ b = a :/\: b a ==> b = Not a \/ b a <=> b = (a ==> b) /\ (b ==> a) Also, if you generalize Sentence a bit you get a really nice formulation of "true". See my paste at http://hpaste.org/13807#a2 -- ryan 2009/1/10

Re: [Haskell-cafe] Re: Monads aren't evil

2009-01-10 Thread Ryan Ingram
My issue is that there seem to be many cases where the syntax extension does *almost* what I want, but not quite. And there isn't any method to extend it, so you are left with two choices: (1) Go back to unsugared syntax (2) Hack your technique into the constraints of the existing syntax exten

Re: [Haskell-cafe] Re: How to give unique name/id to nodes outside any monad ?

2009-01-08 Thread Ryan Ingram
I seem to recall reading somewhere that an object's StableName can change when it becomes evaluated; so it's possible you aren't detecting sharing because of this. You might try this instead: > mkStableName' a = mkStableName $! a This forces the object to become evaluated before calling mkStable

Re: [Haskell-cafe] Re: Blitting one IOUArray into another

2009-01-08 Thread Ryan Ingram
You can't safely convert an IOUArray into a Ptr; Ptr is a raw value which isn't noticed by the garbage collector, so if the data is relocated or GC'd while you have a pointer to it, further access will corrupt memory. Rather, the data inside of an IOUArray is held in a MutableByteArray#. In Data.

Re: [Haskell-cafe] State Monad - using the updated state

2009-01-07 Thread Ryan Ingram
Hi Phil. First a quick style comment, then I'll get to the meat of your question. getRanq1 is correct; although quite verbose. A simpler definition is this: getRanq1 = State ranq1 This uses the State constructor from Control.Monad.State: State :: (s -> (a,s)) -> State s a What it sounds like y

Re: [Haskell-cafe] Template Haskell question

2009-01-07 Thread Ryan Ingram
On Wed, Jan 7, 2009 at 12:58 PM, Jeff Heard wrote: > And how do I encode > > a{ mousePositionf = b } > > in template haskell without using the [| |] syntax, so that I can use mkName? Whenever I have a question like that, I just ask ghci: $ ghci -fth ghci> :m Control.Monad.Identity Language.Haske

Re: [Haskell-cafe] Type Family Relations

2009-01-03 Thread Ryan Ingram
I've been fighting this same problem for a while. The solution I've come up with is to encode the axioms into a typeclass which gives you a proof of the axioms. Here's an excerpt from some code I've been playing around with; HaskTy and Lift are type families. -- Theorem: for all t instance of Li

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2009-01-01 Thread Ryan Ingram
2008/12/31 Paolino : > I must ask why runWriterT k :: State s (a,[Int]) is working. > Looks like I could runIO the same way I evalState there. > In that case I wouldn't wait for the State s action to finish. > > Thanks Assuming you have Control.Monad.State.Lazy (which I think is the default), here

Re: [Haskell-cafe] Updating doubly linked lists

2008-12-31 Thread Ryan Ingram
Also, it's actually really hard to tie the knot in the update; without some kind of distinguished node that allows you to know that it is the beginning/end of the list. For example, in this DList: 1,1,1, lots of times, 1, 2, 1, 1, ... lots of times, 1, (loop) If you change the 3rd "1", how

Re: [Haskell-cafe] WriterT [w] IO is not lazy in reading [w]

2008-12-31 Thread Ryan Ingram
IO is not lazy; you never make it to "print". Consider this program: > k = f 0 where >f n = do >lift (print n) >tell [n] >f (n+1) > weird :: IO [Int] > weird = do > (_, ns) <- runWriterT k > return (take 20 ns) What should "weird" print? According to "k", it

Re: [Haskell-cafe] represent data sturcture using function

2008-12-29 Thread Ryan Ingram
On Mon, Dec 29, 2008 at 4:29 AM, wrote: > Would you please give me a complete example of code that I could have more > information > on the idea? Sure, I put up an example at http://ryani.freeshell.org/haskell/gmap.hs class MapKey k where data (:->) k :: * -> * newMap :: (k -> v) -> (k

Re: [Haskell-cafe] IORef vs TVar performance: 6 seconds versus 4 minutes

2008-12-29 Thread Ryan Ingram
On Mon, Dec 29, 2008 at 7:56 AM, Evan Laforge wrote: > But I thought a haskell RTS was a win for correctness and ease of > modification, but a lose for performance? Thanks for the paper link, > I'll check it out in a bit. There's a seemingly endless supply of > interesting haskell papers out the

Re: [Haskell-cafe] represent data sturcture using function

2008-12-29 Thread Ryan Ingram
Bonus points if you find the stupid bug in my code :) -- ryan On Mon, Dec 29, 2008 at 1:48 AM, Ryan Ingram wrote: > On Sun, Dec 28, 2008 at 10:13 PM, David Menendez wrote: >> 2008/12/29 Raeck chiu : >>> It seems to be very difficult to change the number of Male or Female

Re: [Haskell-cafe] represent data sturcture using function

2008-12-29 Thread Ryan Ingram
On Sun, Dec 28, 2008 at 10:13 PM, David Menendez wrote: > 2008/12/29 Raeck chiu : >> It seems to be very difficult to change the number of Male or Female if a >> concrete data structure is not used. Is it possible change the number of >> Male in classA >> when represent classA using function? > >

Re: [Haskell-cafe] reactive? was Re: Incremental trasnformations (not Haskell topic)

2008-12-29 Thread Ryan Ingram
2008/12/28 Luke Palmer : > Adaptive programming is sortof the opposite of reactive programming, the way > I see it. Adaptive is imperative (that's the best word I have for it), i.e. > you have a bunch of variables and your code decides which one to change. > Whereas reactive programming, at the ve

Re: [Haskell-cafe] IORef vs TVar performance: 6 seconds versus 4 minutes

2008-12-29 Thread Ryan Ingram
On Sun, Dec 28, 2008 at 11:08 PM, Evan Laforge wrote: > But every STM operation has to modify a transaction log, which seems > like it should be even more expensive than frobbing a lock bit. So it > seems like if the per-operation STM overhead is higher, and blocking > contention is the same (ass

Re: [Haskell-cafe] IORef vs TVar performance: 6 seconds versus 4 minutes

2008-12-28 Thread Ryan Ingram
Both readTVar and writeTVar are worse than O(1); they have to look up the TVar in the transaction log to see if you have made local changes to it. Right now it looks like that operation is O(n) where n is the number of TVars accessed by a transaction, so your big transaction which is just accessin

Re: [Haskell-cafe] Re: Incremental trasnformations (not Haskell topic)

2008-12-28 Thread Ryan Ingram
See "Adaptive Functional Programming" by Acar et al. http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.61.2257 Doesn't talk about OO specifically, but rather how to make "updatable" computations in a mutable language. There's a Haskell implementation, too. http://hackage.haskell.org/cgi-bin

Re: [Haskell-cafe] The Applicative Functor Monad

2008-12-24 Thread Ryan Ingram
ons: > evalAF :: Applicative f => AF f x () a -> (f x, a) > evalAF = runAF >>> first (($ ()) <$>) The dual is also potentially useful, where you use (flip (<.>)) instead. I'm not sure if this is useful for Jeremy's goal, but it's an interesting direction t

Re: [Haskell-cafe] Defining a containing function on polymorphic list

2008-12-24 Thread Ryan Ingram
Here's a tip: leave off the type signature, and ask ghci what it is. $ ghci Prelude> let contain x [] = False ; contain x (y:ys) = if x == y then True else contain x ys Prelude> :t contain contain :: (Eq a) => a -> [a] -> Bool -- ryan 2008/12/22 Raeck Zhao : > I am trying to define a containin

Re: [Haskell-cafe] The Applicative Functor Monad

2008-12-24 Thread Ryan Ingram
I think that there's no solution for your problem as stated, besides going with something like type-indexed monads, which leads you down the no-implicit-prelude path. But to see one obvious reason why this is the case: can you tell me what the type of "returnAF" is? Also, one of the monad laws is

Re: [Haskell-cafe] Re: Threads with high CPU usage

2008-12-22 Thread Ryan Ingram
You shouldn't need forkOS, but without -threaded (and related RTS switches to enable multithreading) I think you are sunk. Without enabling multithreading support, you are saying that your program (which might use concurrency features of Haskell) will run on a single OS thread. During a foreign c

Re: [Haskell-cafe] Trouble with the ST monad

2008-12-21 Thread Ryan Ingram
The problem is that you are trying to return a mutable array out of an ST computation. This lets the "mutability" of the computation escape. That's what the "s" type variable is for; without it, runST is just unsafePerformIO. To solve your problem, you need to eliminate any references to the st

Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Ryan Ingram
You have a few options. In Haskell98 (no extensions): a () = (f,f) g () = fst (a ()) -- alternatively g x = fst (a ()) x Here you make it explicit that "a" and "g" are functions; the monomorphism restriction is there to stop things that look like values (and therefore you expect to only get eval

Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Ryan Ingram
heck == 4 bigEndian = endianCheck == 1 -- ryan On Thu, Dec 18, 2008 at 4:33 AM, Ryan Ingram wrote: > I think something like this might work: > > Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x) > 2 > > You should get 1 for big-endian and 2 for littl

Re: [Haskell-cafe] Detecting system endianness

2008-12-18 Thread Ryan Ingram
I think something like this might work: Prelude GHC.Exts GHC.Word> let W64# x = 0x10002 in W32# (unsafeCoerce# x) 2 You should get 1 for big-endian and 2 for little-endian. (Disclaimer: not particularily well-tested.) -- ryan On Thu, Dec 18, 2008 at 3:27 AM, Mauricio wrote: > Hi, > > Is

Re: [Haskell-cafe] Coroutines

2008-12-18 Thread Ryan Ingram
On Thu, Dec 18, 2008 at 3:01 AM, Robin Green wrote: > In my opinion, in Haskell, you don't need coroutines because you have > lazy evaluation. That's a fair criticism. Lazy evaluation basically gives you a coroutine embedded in any data structure. But sometimes making implicit things explicit a

Re: [Haskell-cafe] Coroutines

2008-12-18 Thread Ryan Ingram
On Thu, Dec 18, 2008 at 2:00 AM, Nicolas Pouillard wrote: > I don't see why one would need session types, channels... to express that. > I maybe need a more complicated coroutines (ruby) example that would require > using this system. OK, how would you type these routines in Haskell? def simple

Re: [Haskell-cafe] lengthOP rewrite rules

2008-12-18 Thread Ryan Ingram
2008/12/18 Luke Palmer : > On Thu, Dec 18, 2008 at 1:53 AM, Cetin Sert wrote: >> >> Hi, >> >> I tested the following, why does the rewrite rules not fire when using >> tuples also in testRewrite2, testRewriteReverse2? > >> testRewrite2 :: a → (Bool,Bool) >> testRewrite2 x = (pf,pi) >> where >>

[Haskell-cafe] Coroutines

2008-12-18 Thread Ryan Ingram
Andrew was recently asking about co-routines. A couple of years ago, I was in much the same position as him; although I am pretty sure I had heard the term before, it seemed like a mysterious idea with no practical use. Then I learned Ruby. Ruby makes extensive use of coroutines; it's not uncomm

Re: [Haskell-cafe] How to choose an arbitrary Arbitrary?

2008-12-17 Thread Ryan Ingram
It's absolutely possible. However, I think you do need to enumerate the possible types somehow. Here's an example that demonstrates the idea: > {-# LANGUAGE ScopedTypeVariables #-} > sizedTree :: forall a. Arbitrary a => Int -> Gen (Tree a) > sizedTree n | n <= 0 = liftM Val arbitrary > sizedTre

Re: [Haskell-cafe] Implementing PacMan

2008-12-17 Thread Ryan Ingram
Oops, misread a bit. I thought this was your series of posts, Andrew! But other than that, my points stand :) -- ryan On Wed, Dec 17, 2008 at 12:13 AM, Ryan Ingram wrote: > In the last "episode" you talk about an entity's update being a function like: > >> i

<    1   2   3   4   5   6   7   8   >