Re: [Haskell-cafe] unsafeDestructiveAssign?

2009-08-13 Thread Roberto Zunino
Job Vranish wrote: Does anybody know if there is some unsafe IO function that would let me do destructive assignment? Something like: a = 5 main = do veryUnsafeAndYouShouldNeverEveryCallThisFunction_DestructiveAssign a 8 print a 8 Untested, just guessing: {-# NOILINE aRef , a #-}

Re: [Haskell-cafe] Newbie: Replacing substring?

2008-07-22 Thread Roberto Zunino
Dmitri O.Kondratiev wrote: I wrote my own version, please criticize: -- replace all occurances of 123 with 58 in a string: test = replStr abc123def123gh123ikl 123 58 This is a tricky problem: first of all, you fail your own test! ;-) *Main test abc58def58gh58ikl58 (Note the extra 58 at the

Re: [Haskell-cafe] Mutually recursive modules and google protocol-buffers

2008-07-15 Thread Roberto Zunino
Chris Kuklewicz wrote: There is no way to create a A.hs-boot file that has all of (1) Allows A.hs-boot to be compiled without compiling B.hs first (2) Allows B.hs (with a {-# SOURCE #-} pragma) to be compiled after A.hs-boot (3) Allows A.hs to compiled after A.hs-boot with a consistent

Re: [Haskell-cafe] Typeable and fancy types

2008-07-11 Thread Roberto Zunino
Ron Alford wrote: instance Typeable1 f = Typeable (Expr f) where typeOf (In x) = mkTyConApp (mkTyCon TypeTest.Expr) [typeOf1 x] typeOf ~(In x) = mkTyConApp (mkTyCon TypeTest.Expr) [typeOf1 x] Lazy patterns are jolly useful here. Remember that typeOf will be usually called on _|_,

Re: [Haskell-cafe] Moving forall over type constructors

2008-06-10 Thread Roberto Zunino
Sean Leather wrote: inside :: ((forall a. W (t a))- W (forall a. (t a))) --inside (W x) = W x -- (a) FAILS --inside = W . unW -- (b) FAILS inside x = W (unW x) -- (c) WORKS Are there any pointers for developing a better understanding or intuition of this? Usually, making type arguments

Re: [Haskell-cafe] type-level integers using type families

2008-05-30 Thread Roberto Zunino
Manuel M T Chakravarty wrote: Peter Gavin: will work if the non-taken branch can't be unified with anything. Is this planned? Is it even feasible? I don't think i entirely understand the question. Maybe he wants, given cond :: Cond x y z = x - y - z tt :: True true_exp :: a

Re: [Haskell-cafe] I/O without monads, using an event loop

2008-05-30 Thread Roberto Zunino
Robin Green wrote: I have been thinking about to what extent you could cleanly do I/O without explicit use of the I/O monad, and without uniqueness types Here's a way to see I/O as a pure functional data structure. To keep things simple, we model only Char I/O: data Program = Quit | Output

Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Roberto Zunino
Kim-Ee Yeoh wrote: How about foo :: (exists. m :: * - *. forall a. a - m a) - (m Char, m Bool) Thank you: I had actually thought about something like that. First, the exists above should actually span over the whole type, so it becomes a forall because (-) is contravariant on its 1st

Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Roberto Zunino
Isaac Dupree wrote: foo :: (Char - a /\ Bool - b) - (a,b) a.k.a. find some value that matches both Char-a and Bool-b for some a and b. Could use type-classes to do it. Uhmm... you mean something like (neglecting TC-related issues here) class C a b where fromChar :: Char - a

Re: [Haskell-cafe] Aren't type system extensions fun? [Further analysis]

2008-05-29 Thread Roberto Zunino
Roberto Zunino wrote: Uhmm... you mean something like (neglecting TC-related issues here) class C a b where fromChar :: Char - a fromBool :: Bool - b Oops: i meant something like class C x a b | x - a,b where fromChar :: x - Char - a fromBool :: x - Bool - b Zun

Re: [Haskell-cafe] Re: Aren't type system extensions fun? [Further analysis]

2008-05-28 Thread Roberto Zunino
Andrew Coppin wrote: (id 'J', id True) -- Works perfectly. \f - (f 'J', f True) -- Fails miserably. Both expressions are obviously perfectly type-safe, and yet the type checker stubbornly rejects the second example. Clearly this is a flaw in the type checker. When you type some

Re: [Haskell-cafe] Funny State monad dependency

2008-04-16 Thread Roberto Zunino
Miguel Mitrofanov wrote: It has nothing to do with State; it actually works in List monad. return y is just another way of writing [y]. Actually, it seems that in this case return is from the ((-) a) monad, i.e. return=const. f x y = x = return y = x = const y = (concat . map)

Re: [Haskell-cafe] True parallelism missing :-(

2008-03-25 Thread Roberto Zunino
Dusan Kolar wrote: Dear all, I've thought the following three (dummy) programs would run some of their parts in parallel (on dual core) if compiled with option threaded (smp). The truth is that only the first one exploits multicore CPU. Why? h1 - forkIO $ putMVar v1 $ fibs (n-1)

Re: [Haskell-cafe] Type checking of partial programs

2008-03-20 Thread Roberto Zunino
ac wrote: foo :: [Foo] - placeholder 1 foo xs = map placeholder 2 xs What are the possible type signatures for placeholder 1 and the possible expressions for placeholder 2? A nice GHCi trick I learned from #haskell: :t let foo xs = map ?placeholder2 xs in foo forall a b.

Re: [Haskell-cafe] derivation of mapP, a parallel, lazy map

2008-02-26 Thread Roberto Zunino
Dan Weston wrote: According to Lennart Augustsson (http://haskell.org/pipermail/haskell-cafe/2007-July/029603.html) you can have uninterruptible threads in ghc. If a thread never allocates it will never be preempted. I am aware of that. I think I heard GHC devs acknowledge that it is indeed

Re: [Haskell-cafe] derivation of mapP, a parallel, lazy map

2008-02-25 Thread Roberto Zunino
Felipe Lessa wrote: Have you seen parBuffer? I'd also recommend looking at its source. I wonder if it would be possible to make a variant of parBuffer so that the following evaluates to 1: take 1 $ parBuffer 10 r0 (1:2:3:undefined) *** Exception: Prelude.undefined Maybe we should use a

Re: [Haskell-cafe] A beginners question

2008-02-23 Thread Roberto Zunino
Harri Kiiskinen wrote: fmap (^4) [1,2,3] = \i - shows i let i = fmap (^4) [1,2,3] in shows i Probably very simple, but there must be a delicate difference between these two expressions. I just don't get it. First, let's simplify these expressions using the following equation: fmap

Re: [Haskell-cafe] Windows, or GHC?

2008-02-12 Thread Roberto Zunino
Svein Ove Aas wrote: A program to do this follows for your convenience. #include stdio.h int main() { int i; for (int i=0; i3; i++) puts(Hello\0); This will have the same effect as puts(Hello). Maybe putchar(0) will actually output the NUL. Zun.

Re: [Haskell-cafe] Data.Ord and Heaps (Was: Why functional programming matters)

2008-02-05 Thread Roberto Zunino
(Sorry for the late reply.) [EMAIL PROTECTED] wrote: I'd really like to write class (forall a . Ord p a) = OrdPolicy p where but I guess that's (currently) not possible. Actually, it seems that something like this can be achieved, at some price. First, I change the statement ;-) to

Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-17 Thread Roberto Zunino
Dominic Steinitz wrote: Roberto Zunino wrote: This is the point: eta does not hold if seq exists. undefined `seq` 1 == undefined (\x - undefined x) `seq` 1 == 1 Ok I've never used seq and I've never used unsavePerformIO. Provided my program doesn't contain these then can I assume that eta

Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Roberto Zunino
Yitzchak Gale wrote: When using seq and _|_ in the context of categories, keep in mind that Haskell composition (.) is not really composition in the category-theoretic sense, because it adds extra laziness. Use this instead: (.!) f g x = f `seq` g `seq` f (g x) id .! undefined == \x -

Re: [Haskell-cafe] Questions about the Functor class and it's use in Data types à la carte

2007-12-16 Thread Roberto Zunino
Dominic Steinitz wrote: This would give = \x - bot x and by eta reduction This is the point: eta does not hold if seq exists. undefined `seq` 1 == undefined (\x - undefined x) `seq` 1 == 1 The (.) does not form a category argument should be something like: id . undefined == (\x -

[Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote: server text | Just xs - parse text = let x | field1 `elem` xs = error ... do one thing ... | field2 `elem` xs = error ... do something else ... in x server _ = error ... invalid request ... This now has the wrong semantics - before if parse

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-04 Thread Roberto Zunino
Neil Mitchell wrote: is there any automated way to know when a function is strict in its arguments? Yes, strictness analysis is a very well studied subject - ...and is undecidable, in general. ;-) Zun. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Call external program and get stdout

2007-11-23 Thread Roberto Zunino
Allan Clark wrote: -- Create the process do (_pIn, pOut, pErr, handle) - runInteractiveCommand command -- Wait for the process to finish and store its exit code exitCode - waitForProcess handle Warning: this will get stuck if the command output is so big that it fills the SO

Re: [Haskell-cafe] Polymorphic dynamic typing

2007-11-23 Thread Roberto Zunino
Paulo Silva wrote: Type representations using GADTs are being used to achieve dynamic typing in Haskell. However, representing polymorphic types is problematic. Does anyone know any work about including polymorphism in dynamic typing? First, a warning: fragile code follows, possibly

Re: [Haskell-cafe] Re: Composing monads

2007-11-23 Thread Roberto Zunino
Maurí­cio wrote: main = mapM_ ((putStrLn ) * putStrLn) $ map show [1,2,3] Using only standard combinators: main = mapM_ ((putStrLn ) . putStrLn) $ map show [1,2,3] Zun. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-22 Thread Roberto Zunino
I must confess that I find choosing type Prop = CProp () to be slightly dangerous, since now CProp (const ()) :: Prop p and there is nothing in that expression that suggests non-termination (~ invalid proof). I would rather choose a type admitting only _|_ as its value: type Prop =

Re: [Haskell-cafe] On the verge of ... giving up! [OT]

2007-10-14 Thread Roberto Zunino
[EMAIL PROTECTED] wrote: I will be impolite. There was no need to. Andrew Coppin wrote: OK. I get the message. I'm unsubscribing now... There was no need to. Please, let's keep haskell-cafe a friendly place, as it's always been. When someone posts inaccurate (or even wrong) facts: Attack

Re: [Haskell-cafe] Re: Type-level arithmetic

2007-10-13 Thread Roberto Zunino
Andrew Coppin wrote: I was actually thinking more along the lines of a programming language where you can just write head :: (n 1) = List n x - x Current GHC can approximate this with a GADT: == {-# OPTIONS -fglasgow-exts #-} module SafeHead where

Re: [Haskell-cafe] Manual constructor specialization

2007-10-09 Thread Roberto Zunino
A GADT version seems to generate OK code: data Top data NTop data Rope t where Empty :: Rope Top Leaf :: Rope NTop Node :: !(Rope NTop) - !(Rope NTop) - Rope NTop index :: Rope t - Int - Word8 index Empty _ = error empty index Leaf _ = error leaf index (Node l r) n = index' l n

Re: [Haskell-cafe] Typed DSL compiler, or converting from an existential to a concrete type

2007-10-06 Thread Roberto Zunino
[EMAIL PROTECTED] wrote: we might attempt to write testr = either (error) (ev) (typecheck env0 te3) where ev (TypedTerm t e) = sin (eval e) We know that it should work. If we know it has to be a Double, we can express that: testr = either (error) (ev) (typecheck env0 te3) where ev

[Haskell-cafe] Re: [Haskell] Seemingly impossible Haskell programs

2007-09-29 Thread Roberto Zunino
Graham Hutton wrote: Readers of this list may enjoy the following note by Martin Escardo, which shows how to write a number of seemingly impossible Haskell programs that perform exhaustive searches over spaces of infinite size, by exploiting some ideas from topology:

Re: [Haskell-cafe] Why isn't pattern matching lazy by default?

2007-09-19 Thread Roberto Zunino
Henning Thielemann wrote: Then why are patterns in lambdas not lazy? Because they should allow for more branches! ;-)) null = \ [] - True _ - False -- Zun. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Haddock/hscolour integration broken on Hackage?

2007-09-12 Thread Roberto Zunino
Malcolm Wallace wrote: David Menendez [EMAIL PROTECTED] writes: I was looking at the Data.Binary documentation[1] on Hackage, and I've noticed some problems with the associated source listings[2]. First, none of the Source links work. They all refer to fragment IDs (e.g., #Binary) that are

Re: [Haskell-cafe] Haddock/hscolour integration broken on Hackage?

2007-09-12 Thread Roberto Zunino
Roberto Zunino wrote: Would be enough to use the %xx encoding of parenthesis? Would you instead use another prefix (it is enough that no haskell identifier can start with it)? Maybe .line or -line ? AFAICS, I think line- should do. From w3.org: ID and NAME tokens must begin with a letter

Re: [Haskell-cafe] Re: Existentials and type var escaping

2007-06-23 Thread Roberto Zunino
Ben Rudiak-Gould wrote: It's not definable, and there is a good reason. Existential boxes in principle contain an extra field storing their hidden type, and the type language is strongly normalizing. Thank you very much for the answer: indeed, I suspected strong normalization for types had

Re: [Haskell-cafe] Messing around with types [newbie]

2007-06-21 Thread Roberto Zunino
Cristiano Paris wrote: class FooOp a b where foo :: a - b - IO () instance FooOp Int Double where foo x y = putStrLn $ (show x) ++ Double ++ (show y) partialFoo = foo (10::Int) bar = partialFoo (5.0::Double) The Haskell type classes system works in an open world assumption: while the

Re: [Haskell-cafe] dangerous inlinePerformIO in Data.Binary(?)

2007-06-17 Thread Roberto Zunino
Udo Stenzel wrote: | toLazyByteString :: Builder - L.ByteString | toLazyByteString m = S.LPS $ inlinePerformIO $ do | buf - newBuffer defaultSize | return (runBuilder (m `append` flush) (const []) buf) Why is this safe? Considering the GHC implementation of IO, isn't there a real

Re: [Haskell-cafe] Language extensions

2007-05-31 Thread Roberto Zunino
Tomasz Zielonka wrote: On Wed, May 30, 2007 at 11:21:45PM +0200, Roberto Zunino wrote: ($!) Data.List.repeat -- ;-) unbounded types You got me - I'm not sure how to respond to that. Let's try: this function doesn't preserve computable equality. Ah, silly me! I checked that inequality

[Haskell-cafe] Existentials and type var escaping

2007-05-31 Thread Roberto Zunino
In this function data C = C Int foo :: C - C foo ~(C x) = C x foo is _not_ the identity: its result must be non bottom, i.e. the constructor C is forced to its argument. I wonder if a similar function is definable for existential types: data E = forall a . E a foo :: E - E foo, as defined

Re: [Haskell-cafe] Language extensions

2007-05-30 Thread Roberto Zunino
Tomasz Zielonka wrote: In the Ord variant, the result value pretty much has to come from the input list or be bottom. It has to be bottom for the empty list. If f :: Ord a = [a] - a and g preserves order (is monotonic) then f (map g l) == g (f l) This could be nice for testing Ord

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Roberto Zunino
(re-joining the list -- I forgot to reply all) Vincent Kraeutler wrote: Roberto Zunino wrote: Vincent Kraeutler wrote: i see that the definition of fix (from Control.Monad.Fix) could not be any simpler: fix f = let x = f x in x I actually consider fix f = f (fix f) to be simpler. Alas

Re: [Haskell-cafe] Bug in GADT Implementation?

2007-05-26 Thread Roberto Zunino
Dominic Steinitz wrote: I would expect foo r@(Range BITSTRING _ _) x = [] to give an error but it doesn't. Writing t = Range BITSTRING gives one so why not the pattern match? AFAICS, this is because when you construct a value, as in t, you have to provide the required context (Ord in

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Andrew Coppin wrote: Right. So what you're saying is that for most program properties, you can partition the set of all possible problems into the set for which X is true, the set for which X is false, and a final set for programs where we can't actually determine the truth of X. Is that about

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Christopher L Conway wrote: On 5/14/07, Roberto Zunino [EMAIL PROTECTED] wrote: Also, using only rank-1: polyf :: Int - a - Int polyf x y = if x==0 then 0 else if x==1 then polyf (x-1) (\z-z) else polyf (x-2) 3 Here passing both 3 and (\z-z) as y confuses the type

Re: [Haskell-cafe] Limits of deduction

2007-05-14 Thread Roberto Zunino
Matthew Brecknell wrote: Roberto Zunino: Here passing both 3 and (\z-z) as y confuses the type inference. So the type inference is not really confused at all. It just gives a not-very-useful type. Yes, you are right, I didn't want to involve type classes and assumed 3::Int. A better

Re: [Haskell-cafe] Code layout in Emacs' haskell-mode

2007-05-14 Thread Roberto Zunino
Nick Meyer wrote: main = do putStrLn Enter a number: inp - getLine let n = read inp if n == 0 then putStrLn Zero else putStrLn NotZero (that's with all the expressions in the do block lining up vertically, if that doesn't show up in a fixed-width

[Haskell-cafe] Safe top-level IORefs

2007-03-04 Thread Roberto Zunino
I'm posting the code of a module, IORefs, allowing top-level IORefs to be safely declared and used. Usafety reports are welcome. Tested in GHC 6.6. ** Features: 1) IORef a provided for any Typeable a 2) An unbounded number of IORef's can be declared 3) An IORef declaration is 3 lines long (+

Re: [Haskell-cafe] Safe top-level IORefs

2007-03-04 Thread Roberto Zunino
Neil Mitchell wrote: Hi On 3/4/07, Roberto Zunino [EMAIL PROTECTED] wrote: I'm posting the code of a module, IORefs, allowing top-level IORefs to be safely declared and used. Usafety reports are welcome. Tested in GHC 6.6. That looks cool, does it work on Hugs? I've tested it right now

[Haskell-cafe] Non-exported type classes?

2007-03-03 Thread Roberto Zunino
where instance Peano Z where instance Peano a = Peano (S a) where -- Exported class Peano a = C a where === Would that limit the instances of the class C to the Peano type naturals? Thanks, Roberto Zunino. ___ Haskell-Cafe mailing list Haskell-Cafe

Re: [Haskell-cafe] Trouble understanding records and existential types

2007-01-27 Thread Roberto Zunino
Brian Hulley wrote: Chris Kuklewicz wrote: This is how I would write getLeaves, based on your GADT: data IsLeaf data IsBranch newtype Node = Node { getNode :: (forall c. ANode c) } [snip] Thanks Chris - that's really neat! I see it's the explicit wrapping and unwrapping of the existential

Re: [Haskell-cafe] restricted existential datatypes

2007-01-10 Thread Roberto Zunino
Misha Aizatulin wrote: The question I'd like to ask is whether there is some trickery to circumvent this problem. In the f function I'd like to be able to hint to the compiler that I want Show to be derived from cxt which is attached to the Box, but I see no way of doing that. An explicit

Re: [Haskell-cafe] GADTs are expressive

2007-01-08 Thread Roberto Zunino
Robin Green wrote: Well, not really - or not the proof you thought you were getting. As I am constantly at pains to point out, in a language with the possibility of well-typed, non-terminating terms, like Haskell, what you actually get is a partial proof - that *if* the expression you are

Re: [Haskell-cafe] MVar style question

2007-01-04 Thread Roberto Zunino
unnecessary locks. If alice2 only needs a, why should she be blocked from bob2 using only b? This issue gets worse once one starts using MVar (A,B,C,...), or MVar [A]. So, the solution is: choose wisely! ;-) Regards, Roberto Zunino. ___ Haskell-Cafe

Re: [Haskell-cafe] Redefining superclass default methods in a subclass

2007-01-04 Thread Roberto Zunino
Brian Hulley wrote: Hi, Looking at some of the ideas in http://www.haskell.org/haskellwiki/The_Other_Prelude , it struck me that the class system at the moment suffers from the problem that as hierarchies get deeper, the programmer is burdened more and more by the need to cut-and-paste

[Haskell-cafe] Monad Set via GADT

2007-01-03 Thread Roberto Zunino
as non-GADT related alternative approaches. Regards, Roberto Zunino. \begin{code} {-# OPTIONS_GHC -Wall -fglasgow-exts #-} module SetMonad ( SetM() , toSet, fromSet , union, unions , return', mzero' ) where import

[Haskell-cafe] GADT proofs of FunDeps?

2007-01-03 Thread Roberto Zunino
? Regards, Roberto Zunino. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] [Redirect] polymorphism and existential types

2006-11-30 Thread Roberto Zunino
, (where t might depend on a). Regards, Roberto Zunino. signature.asc Description: OpenPGP digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] What's up with this Haskell runtime error message:

2006-04-06 Thread Roberto Zunino
. and eventually all the variables could be defined. Another example: the pair constructor (,) is lazy so c = (3, fst c) -- loop on c is OK, and defines c=(3,3). Regards, Roberto Zunino. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

Re: [Haskell-cafe] What's up with this Haskell runtime error message:

2006-04-05 Thread Roberto Zunino
Michael Goodrich wrote: [snip] r = r2+2*step*rdc rdc = (rd2+rd1+rd0)/6 rd0 = c0*c0*m c0 = baz(z0) z0 = 6.378388e6-r The equations above form a loop: each one requires the one below it, and the last one requires the first one. (And yes, baz is strict) Regards, Roberto

Re: [Haskell-cafe] More STUArray questions

2006-03-13 Thread Roberto Zunino
. As it happens for (x + y) = (+) x y , the parser read (forall s . t) as (.) (forall s) t Also, forall was parsed as a type variable rather than the universal quantifier keyword. Try compiling with -fglasgow-exts . Regards, Roberto Zunino. ___ Haskell

Re: [Haskell-cafe] Tree with collections

2006-03-11 Thread Roberto Zunino
show (CollNode n) = CollNode ++ show n *CollTree show (CollNode [CollNode [],CollNode []]) CollNode [CollNode [],CollNode []] However, I can not figure why the typechecker does not loop here (GHC 6.4.1). Regards, Roberto Zunino. ___ Haskell-Cafe

Re: [Haskell-cafe] Monad strictness

2005-11-21 Thread Roberto Zunino
Yitzchak Gale wrote: In the following, why does testA work and testB diverge? Where is the strictness coming from? My guess: from strict pattern matching in (=). The following StateT variant uses lazy (irrefutable) pattern match instead. Regards, Roberto Zunino. newtype StT s m