Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-06 Thread Tillmann Rendel
Hi, Ryan Newton wrote: It is very hard for me to see why people should be able to make their own Generic instances (that might lie about the structure of the type), in Safe-Haskell. I guess that lying Generics instances might arise because of software evolution. Let's say we start with an

Re: [Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

2013-10-02 Thread Tillmann Rendel
Hi, Roman Cheplyaka wrote: It still seems to fit nicely into Safe Haskell. If you are the implementor of an abstract type, you can do whatever you want in the Eq instance, declare your module as Trustworthy, and thus take the responsibility for soundness of that instance w.r.t. your public API.

Re: [Haskell-cafe] Why isn't hsc2hs functionality provided by ghc?

2013-06-05 Thread Tillmann Rendel
Hi, Roman Cheplyaka wrote: My preferred solution would be to have ghc/ghci automatically run hsc2hs [...] when necessary. How about having a `ghci` command for cabal? I don't think cabal can provide that. Let's say you're inside a 'cabal ghci' session. If you modify the hsc file and reload

Re: [Haskell-cafe] GADT and instance deriving

2013-05-25 Thread Tillmann Rendel
Hi, TP wrote: Today I have a type constructor Tensor in which there is a data constructor Tensor (among others): data Tensor :: Nat - * where [...] Tensor :: String - [IndependentVar] - Tensor order [...] The idea is that, for example, I may have a vector

Re: [Haskell-cafe] rip in the class-abstraction continuum

2013-05-20 Thread Tillmann Rendel
Hi, Christopher Howard wrote: class XyConv a where toXy :: a b - [Xy b] [...] I can get a quick fix by adding Floating to the context of the /class/ definition: class XyConv a where toXy :: Floating b = a b - [Xy b] But what I really want is to put Floating in the context of the

Re: [Haskell-cafe] Propositions in Haskell

2013-05-17 Thread Tillmann Rendel
Hi, Patrick Browne wrote: In am trying to understand why some equations are ok and others not. I suspect that in Haskell equations are definitions rather than assertions. Yes. Haskell function definitions look like equations, but in many ways, they aren't. Here is an example for an equation

Re: [Haskell-cafe] Hackage checking maintainership of packages

2013-05-06 Thread Tillmann Rendel
Hi, Petr Pudlák wrote: -- Forwarded message -- From: *Niklas Hambüchen* m...@nh2.me mailto:m...@nh2.me Date: 2013/5/4 ... I would even be happy with newhackage sending every package maintainer a quarterly question Would you still call your project X

Re: [Haskell-cafe] Hackage checking maintainership of packages

2013-05-06 Thread Tillmann Rendel
Hi, Niklas Hambüchen wrote: Having the metrics you mention is nice, but still they are just metrics and say little the only thing that's important: Is there a human who commits themselves to this package? I like the idea of displaying additional info about the status of package

Re: [Haskell-cafe] Prolog-style patterns

2013-04-08 Thread Tillmann Rendel
Hi, Jan Stolarek wrote: If Haskell allowed to write pattern matching similar to Prolog then we could write this function like this: member :: Eq a = a - [a] - Bool member _ [] = False member x (x:_) = True member x (_:xs) = member x xs The meaning of pattern in the second equation is

Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Tillmann Rendel
Hi, Ömer Sinan Ağacan wrote: One thing I'm not happy about my Haskell programs is, almost all of my programs have a monad transformer stack consisting MonadError, MonadIO and MonadState. You can try to write most of your program in pure functions that are called from a few main functions in

Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-04 Thread Tillmann Rendel
Hi, Richard A. O'Keefe wrote: As I understand it, in ML, it seemed to be a clever idea to not have type signatures at all. Wrong. In ML, it seemed to be a clever idea not to *NEED* type signatures, and for local definitions they are very commonly omitted. In the ML I used, I remember that

Re: [Haskell-cafe] ANNOUNCE: antiquoter-0.1.0.0

2013-04-04 Thread Tillmann Rendel
Hi, L Corbijn wrote: I'm happy to announce the release of my first package antiquoter, a combinator library for writing quasiquoters and antiquoters. The main aim is to simplify their definitions and reduce copy-and-paste programming. Very interesting. I'm using something similar to your EP

Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-03 Thread Tillmann Rendel
Hi Johannes, Johannes Waldmann wrote: I absolutely dislike it when I have to jump through hoops to declare types in the most correct way, and in the most natural places. reverse :: forall (a :: *) . [a] - [a] \ (xs :: [Bool]) - ... All of this just because it seemed, at some time, a clever

Re: [Haskell-cafe] Haskell is a declarative language? Let's see how easy it is to declare types of things.

2013-04-03 Thread Tillmann Rendel
Hi Kim-Ee, Kim-Ee Yeoh wrote: [...] I guess this is related to your view of [...] Do you have a reference to the previous conversation? Sorry, I mean related to one's view of, not related to Johannes Waldmanns' view of. Which seems miles away from what you're alluding to. Full-blown

Re: [Haskell-cafe] Conflicting bindings legal?!

2013-02-26 Thread Tillmann Rendel
Hi, Andreas Abel wrote: To your amusement, I found the following in the Agda source: abstractToConcreteCtx :: ToConcrete a c = Precedence - a - TCM c abstractToConcreteCtx ctx x = do scope - getScope let scope' = scope { scopePrecedence = ctx } return $ abstractToConcrete (makeEnv

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Tillmann Rendel
Hi Martin, Martin Drautzburg wrote: Note that the left recursion is already visible in the grammar above, no need to convert to parser combinators. The problem is that the nonterminal Exp occurs at the left of a rule for itself. Just a silly quick question: why isn't right-recursion a similar

Re: [Haskell-cafe] Parser left recursion

2013-02-24 Thread Tillmann Rendel
Hi, Kim-Ee Yeoh wrote: Perhaps you meant /productive/ corecursion? Because the definition A ::= B A you gave is codata. If you write a recursive descent parser, it takes the token stream as an input and consumes some of this input. For example, the parser could return an integer that says

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Tillmann Rendel
Hi, Martin Drautzburg wrote: As an exercise I am writing a parser roughly following the expamples in Graham Hutton's book. The language contains things like: data Exp = Lit Int -- literal integer | Plus Exp Exp So the grammar is: Exp ::= Int | Exp + Exp My naive parser

Re: [Haskell-cafe] Parser left recursion

2013-02-20 Thread Tillmann Rendel
Hi, Roman Cheplyaka wrote: Another workaround is to use memoization of some sort — see e.g. GLL (Generalized LL) parsing. Is there a GLL parser combinator library for Haskell? I know about the gll-combinators for Scala, but havn't seen anything for Haskell. Bonus points for providing the

Re: [Haskell-cafe] lambda case (was Re: A big hurray for lambda-case (and all the other good stuff))

2013-01-01 Thread Tillmann Rendel
Hi, Brandon Allbery wrote: [...] syntax extension [...] I think someone's already working on this (SugarHaskell?). Yes, we are working on it. See our paper [1] and Sebastian's talk [2] at the Haskell Symposium. Our current prototype can be installed as an Eclipse plugin [3] or as a

Re: [Haskell-cafe] Categories (cont.)

2012-12-21 Thread Tillmann Rendel
Hi, Christopher Howard wrote: instance Category ... The Category class is rather restricted: Restriction 1: You cannot choose what the objects of the category are. Instead, the objects are always all Haskell types. You cannot choose anything at all about the objects. Restriction 2: You

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-05 Thread Tillmann Rendel
Hi Joerg, Joerg Fritsch wrote: I am interested in the definition of deep vs shallow embedded I would say: In shallow embedding, a DSL is implemented as a library. Every keyword of the DSL is a function of the library. The implementation of the function directly computes the result of

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-04 Thread Tillmann Rendel
Hi, Joerg Fritsch wrote: is a shallow embedded DSL == an internal DSL and a deeply embedded DSL == an external DSL or the other way around? I mean internal == embedded, independently of deep vs. shallow, following Martin Fowler [1]. Tillmann [1]

Re: [Haskell-cafe] Design of a DSL in Haskell

2012-12-03 Thread Tillmann Rendel
Hi, Joerg Fritsch wrote: I am working on a DSL that eventuyally would allow me to say: import language.cwmwl main = runCWMWL $ do eval (isFib::, 1000, ?BOOL) I have just started to work on the interpreter-function runCWMWL and I wonder whether it is possible to escape to real Haskell

Re: [Haskell-cafe] Monads

2012-09-30 Thread Tillmann Rendel
Vasili I. Galchin wrote: I would an examples of monads that are pure, i.e. no side-effects. One view of programming in monadic style is: You call return and = all the time. (Either you call it directly, or do notation calls it for you). So if you want to understand whether a monad has

Re: [Haskell-cafe] [ANNOUNCE] Fmark markup language

2012-09-18 Thread Tillmann Rendel
Hi, José Lopes wrote in an earlier email: I want to find a natural way of not burdening the user with the task of having to learn some special syntax in order to write a document. And then: [...] we can leave for quoting and use the ' for something else. That sounds like 'some special

Re: [Haskell-cafe] Tutorial: Haskell for the Evil Genius

2012-09-16 Thread Tillmann Rendel
Hi, Kristopher Micinski wrote: Everyone in the Haskell cafe probably has a secret dream to give the best five minute monad talk. (1) Most programming languages support side effects. There are different kinds of side effects such as accessing mutable variables, reading files, running in

Re: [Haskell-cafe] map over Bijections

2012-08-27 Thread Tillmann Rendel
Hi, Sergey Mironov wrote: I need map equivalent for Bijection type which is defined in fclabels: data Bijection (~) a b = Bij { fw :: a ~ b, bw :: b ~ a } instance Category (~) = Category (Bijection (~)) where ... I can define this function as follows: mapBij :: Bijection (-) a c - Bijection

Re: [Haskell-cafe] Fwd: 'let' keyword optional in do notation?

2012-08-09 Thread Tillmann Rendel
Hi, Martijn Schrage wrote: Would expanding each let-less binding to a separate let feel more sound to you? That was actually my first idea, but then two declarations at the same level will not be in the same binding group, so do x = y y = 1 would not compile. This would create a

Re: [Haskell-cafe] 3 level hierarchy of Haskell objects

2012-08-09 Thread Tillmann Rendel
Hi, Patrick Browne wrote: Haskell type classes seem to be signature only (no equations, ignoring default methods) so in general they provide an empty theory with no logical consequences. Note that many type classes in Haskell have equations annotated as comments. For example, the monad laws

Re: [Haskell-cafe] Monads with The contexts?

2012-07-12 Thread Tillmann Rendel
Hi, Takayuki Muranushi wrote: sunPerMars :: [Double] sunPerMars = (/) $ sunMass * marsMass Sadly, this gives too many answers, and some of them are wrong because they assume different Earth mass in calculating Sun and Mars masses, which led to inconsistent calculation. This might be related

Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-27 Thread Tillmann Rendel
Hi Rico, Rico Moorman wrote: data Tree = Leaf Integer | Branch (Tree Integer) (Tree Integer) amount:: Tree - Integer amount (Leaf x) = x amount (Branch t1 t2) = amountt1 + amountt2 [...] additional requirement: If the command-line flag --multiply is set, the function amount computes

Re: [Haskell-cafe] Martin Odersky on What's wrong with Monads

2012-06-26 Thread Tillmann Rendel
Hi, MightyByte wrote: Of course every line of your program that uses a Foo will change if you switch to IO Foo instead. But we often have to also change lines that don't use Foo at all. For example, here is the type of binary trees of integers: data Tree = Leaf Integer | Branch (Tree

Re: [Haskell-cafe] ANNOUNCE: set-monad

2012-06-22 Thread Tillmann Rendel
Hi George, thanks for your detailed reply. George Giorgidze wrote: The key to the approach used in set-monad is to make progress with the evaluation of the unconstrained constructors (i.e., Return, Bind, Zero and Plus) without using constrained set-specific operations. It turns out that for

Re: [Haskell-cafe] The Layout Rule

2012-06-21 Thread Tillmann Rendel
Hi Michael, Michael D. Adams wrote: I am looking for background material on how GHC and other Haskell compilers implement the layout rule. In the context of our work on syntactic extensibility, we have implemented a declarative and extensible mechanism to specify and implement layout rules.

Re: [Haskell-cafe] ANNOUNCE: set-monad

2012-06-17 Thread Tillmann Rendel
Hi, David Menendez wrote: As you noticed, you can get somewhat better performance by using the combinators that convert to S.Set internally, because they eliminate redundant computations later on. Somewhat better? My example was three times faster, and I guess that the fast variant is O(n)

Re: [Haskell-cafe] ANNOUNCE: set-monad

2012-06-16 Thread Tillmann Rendel
Hi George, George Giorgidze wrote: I would like to announce the first release of the set-monad library. On Hackage: http://hackage.haskell.org/package/set-monad Very cool. Seems to work fine. But I am wondering about the impact of using your package on asymptotic complexity (and thereby, on

Re: [Haskell-cafe] Typed TemplateHaskell?

2012-05-23 Thread Tillmann Rendel
Hi Ilya, Ilya Portnov wrote: As far as can I see, using features of last GHC one could write typed TH library relatively easily, and saving backwards compatibility. For example, now we have Q monad and Exp type in template-haskell package. Let's imagine some new package, say

Re: [Haskell-cafe] ANN: unfoldable-0.4.0

2012-04-26 Thread Tillmann Rendel
Hi, Sjoerd Visscher wrote: Just as there's a Foldable class, there should also be an Unfoldable class. This package provides one: class Unfoldable t where unfold :: Unfolder f = f a - f (t a) Just to be sure: That's not a generalization of Data.List.unfoldr, or is it somehow?

Re: [Haskell-cafe] I Need a Better Functional Language!

2012-04-05 Thread Tillmann Rendel
Paul R wrote: I am curious what are interesting use-cases for that? Symbolic analysis? self-compilers? Optimization. For example, imagine the following definition of function composition: map f . map g = map (f . g) f . g = \x - f (g x) In Haskell, we cannot write this, because we

Re: [Haskell-cafe] Are there arithmetic composition of functions?

2012-03-20 Thread Tillmann Rendel
Hi, sdiy...@sjtu.edu.cn wrote: I feel it would be very natural to have in haskell something like g::Float-Float --define g here h::Float-Float --define h here f::Float-Float f = g+h --instead of f t = g t+h t --Of course, f = g+h is defined as f t = g t+h t One

Re: [Haskell-cafe] Theoretical question: are side effects necessary?

2012-03-16 Thread Tillmann Rendel
Hi, Christopher Svanefalk wrote: Are there any problems which *cannot* be solved a side effect-free language (such as Haskell)? No. Haskell is expressive enough. One way to prove that is to implement an interpreter for a language with side effects in Haskell. Now if there's a program P to

Re: [Haskell-cafe] puzzling polymorphism behavior (7.0.3 windows)

2012-03-15 Thread Tillmann Rendel
Hi, this is one of the reasons why unsafePerformIO is not type-safe. Lets see what's going on by figuring out the types of the various definitions. cell = unsafePerformIO $ newIORef [] newIORef returns a cell which can hold values of the same type as its arguments. The type of the empty

Re: [Haskell-cafe] ANN: exists-0.1

2012-02-06 Thread Tillmann Rendel
Hi, Gábor Lehel wrote: data E = forall a. C a = E a I don't know if anyone's ever set out what the precise requirements are for a type class method to be useful with existentials. More than you seem to think. For example: data Number = forall a . Num a = Number a foo :: Number - Number

Re: [Haskell-cafe] If you'd design a Haskell-like language, what would you do different?

2011-12-20 Thread Tillmann Rendel
Hi, Robert Clausecker wrote: Image you would create your own language with a paradigm similar to Haskell or have to chance to change Haskell without the need to keep any compatibility. What stuff would you add to your language, what stuff would you remove and what problems would you solve

Re: [Haskell-cafe] Putting constraints on internal type variables in GADTs

2011-11-08 Thread Tillmann Rendel
Hi, Anupam Jain wrote: -- My datatype data T o where Only ∷ o → T o TT ∷ T o1 → (o1 → o2) → T o2 -- Show instance for debugging instance Show o ⇒ Show (T o) where show (Only o) = Only ⊕ (show o) show (TT t1 f) = TT ( ⊕ (show t1) ⊕ ) As you noticed, the last line doesn't work

Re: [Haskell-cafe] Proposal: remove Stability from haddock documentation on hackage

2011-06-07 Thread Tillmann Rendel
Hi, James Cook wrote: As far as Control.Applicative, I'm not sure to what package you're referring. That label doesn't apply to modules, it applies to packages, and Control.Applicative is a part of the base package (which is not labeled experimental). On

Re: [Haskell-cafe] representing spreadsheets

2011-05-27 Thread Tillmann Rendel
Hi, Eric Rasmussen wrote: The spreadsheet analogy isn't too literal as I'll be using this for data with a more regular structure. For instance, one grid might have 3 columns where every item in column one is a CellStr, every item in column two a CellStr, and every item in column 3 a CellDbl,

Re: [Haskell-cafe] object oriented technique

2011-03-30 Thread Tillmann Rendel
Hi, Steffen Schuldenzucker wrote: data Shape = Shape { draw :: String copyTo :: Double - Double - Shape } Tad Doxsee wrote: Suppose that the shape class has 100 methods and that 1000 fully evaluated shapes are placed in a list. The above solution would store the full method table

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-17 Thread Tillmann Rendel
Hi, Daniel Fischer wrote: Let's look at the following code: countdown n = if n == 0 then 0 else foo (n - 1) s/foo/countdown/ presumably if' c t e = if c then t else e countdown' n = if' (n == 0) 0 (foo (n - 1)) s/foo/countdown'/ Yes to both substitutions. Looks like I

Re: [Haskell-cafe] Type trickery

2011-03-16 Thread Tillmann Rendel
Hi Andrew, Andrew Coppin wrote: You could define a function: withContainer ∷ (∀ s. Container s → α) → α which creates a container, parameterizes it with an 's' that is only scoped over the continuation and applies the continuation to the created container. Hmm, yes. That will work, but I

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
Hi, Yves Parès wrote: A question recently popped into my mind: does lazy evaluation reduce the need to proper tail-recursion? I mean, for instance : fmap f [] = [] fmap f (x:xs) = f x : fmap f xs Here fmap is not tail-recursive, but thanks to the fact that operator (:) is lazy, I think that

Re: [Haskell-cafe] Lazy evaluation and tail-recursion

2011-03-16 Thread Tillmann Rendel
Hi, Daniel Fischer wrote: data EvaluatedList a = Cons a (List a) | Empty type List a = () - EvaluatedList a map :: (a - b) - (List a - List b) map f xs = \_ - case xs () of Cons x xs - Cons (f x) (\_ - map f xs ())

Re: [Haskell-cafe] Question on a common pattern

2011-03-15 Thread Tillmann Rendel
Hi, Donn Cave wrote: someIO= f where f Opt1 = ... I like this ... or, I would like it, if I could make it work! I get The last statement in a 'do' construct must be an expression, Where-clauses can only be used on equations, not on expressions or statements, so you would need

Re: [Haskell-cafe] Examples for the problem

2011-03-02 Thread Tillmann Rendel
Hi, Robert Clausecker wrote: Each instruction has up to three operands, looking like this: @+4 (Jump for bytes forward) foo (the string foo '0'(1+2) etc. A string literal may contain anything but a newline, (there are no escape codes or similar). But when I add a check for a

Re: [Haskell-cafe] Rebindable 'let' for observable sharing?

2011-03-01 Thread Tillmann Rendel
Hi, Bas van Dijk wrote: For the record: are you talking about rewriting: let f = e in b into something like: (\f - e) `letin` (\f - b) where `letin` can be overloaded (rebinded is probably the better term) and has the default implementation: letin :: (a - a) - (a - b) - b fe `letin`

Re: [Haskell-cafe] Performance difference between ghc and ghci

2011-02-22 Thread Tillmann Rendel
Hi, C K Kashyap wrote: I missed out the optimization bit yes, that would make a difference. However beyond that is it not just about graph reduction which should be the same? Even if the number of reduction steps is the same, the bytecode interpreter is still slower than compiled code,

Re: [Haskell-cafe] Proving correctness

2011-02-14 Thread Tillmann Rendel
Pedro Vasconcelos wrote: This is because all input and output data flow is type checked in a function application, whereas imperative side effects might escape checking. For example, the type signature for a variable swapping procedure in C: void swap(int *a, int *b) This will still

Re: [Haskell-cafe] combined parsing pretty-printing

2011-01-26 Thread Tillmann Rendel
Hi Ozgur, Ozgur Akgun wrote: I can write (separately) a parser and a pretty-printer [...] Is there any work to combine the two? Brent Yorgey wrote: Maybe take a look at Invertible Syntax Descriptions: Unifying Parsing and Pretty Printing by Tillmann Rendel and Klaus Ostermann from last

Re: [Haskell-cafe] Reader monad

2010-12-29 Thread Tillmann Rendel
Hi, Michael Rice wrote: I think of (r - m a) as a type signature and Int or Bool by themselves as types. So, all type signatures are themselves types? Yes. In Haskell, functions are first class, so function types like (r - m a) are themselves types. Tillmann

Re: [Haskell-cafe] Template Haskell a Permanent solution?

2010-12-28 Thread Tillmann Rendel
Hi, Jonathan Geddes wrote: For TH use #1, compile-time parsing of arbitrary strings, I think it would be nice for quasiquote semantics to be modified so that code like json :: String - JsonObject json = ... data = [ json | { name : Jonathan , favorite language: Haskell } |]

Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Tillmann Rendel
Hi John, John Smith wrote: Perhaps pattern match failures in a MonadPlus should bind to mzero - I believe that this is what your example and similar wish to achieve. You updated the proposal to say: a failed pattern match should error in the same way as is does for pure code, while in

Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-15 Thread Tillmann Rendel
John Smith proposed: a failed pattern match should error in the same way as is does for pure code, while in MonadPlus, the current behaviour could be maintained with mzero Lennart Augustsson wrote: Any refutable pattern match in do would force MonadFail (or MonadPlus if you prefer). I guess

Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-14 Thread Tillmann Rendel
Hi, John Smith wrote: I would like to formally propose that Monad become a subclass of Applicative A lot of code would break because of this change, but all problems should be reported at compile time, and are easy to fix. In most of the cases, either adding obvious Functor and Applicative

Re: [Haskell-cafe] Re: Re: Reply-To: Header in Mailinglists

2010-11-23 Thread Tillmann Rendel
Hi, Nick Bowler wrote: There is another header, Mail-Followup-To, which tells MUAs to also drop the To and CC lists. Interesting. So is it a good idea to use Mail-Followup-To to move a discussion from one list to another? To: hask...@haskell.org CC: haskell-cafe@haskell.org

Re: [Haskell-cafe] Musings on type systems

2010-11-20 Thread Tillmann Rendel
Hi Andrew, Andrew Coppin wrote: Now, what about type variables? What do they do? Well now, that seems to be slightly interesting, since a type variable holds an entire type (whereas normal program variables just hold a single value), and each occurrance of the same variable is statically

Re: [Haskell-cafe] Musings on type systems

2010-11-20 Thread Tillmann Rendel
Ketil Malde wrote: data Sum a b = A a | B b -- values = values in a + values in b data Prod a b = P a b-- values = values in a * values in b I guess this makes [X] an exponential type, although I don't remember seeing that term :-) I would expect the exponential type to be (a - b):

Re: [Haskell-cafe] Reply-To: Header in Mailinglists

2010-11-19 Thread Tillmann Rendel
Hi Bastian, Bastian Erdnüß wrote: It would make my life a little bit more easy if the mailing lists on haskell.org would add a Reply-To: header automatically to each message containing the address of the mailing list, the message was sent to. Usually that's the place where others would want to

[Haskell-cafe] Re: [Haskell] intent-typing

2010-11-16 Thread Tillmann Rendel
Hi, Marcus Sundman wrote: Hi, how would one go about implementing (or using if it's supported out-of-the-box) intent-typing* for haskell? A basic technique is to use newtype declarations to declare separate types for separate intents. module StringSafety ( SafeString ()

Re: [Haskell-cafe] Serialization of (a - b) and IO a

2010-11-13 Thread Tillmann Rendel
Andrew Coppin wrote: [...] if you could send a block of code from one PC to another to execute it remotely. Eden can do this. http://www.mathematik.uni-marburg.de/~eden/ Eden is a distributed Haskell: You run multiple copies of the same binary on different machines, and you have the (#)

Re: [Haskell-cafe] Re: ANNOUNCE zeno 0.1.0

2010-11-13 Thread Tillmann Rendel
Will Sonnex wrote: Zeno is a fully automated inductive theorem proving tool for Haskell programs. I tried it via the web interface, and it seems to be quite cool. Good work! However: You can express a property such as takeWhile p xs ++ dropWhile p xs === xs and it will prove it to be true

Re: [Haskell-cafe] Most popular haskell applications

2010-11-06 Thread Tillmann Rendel
Ivan Lazar Miljenovic wrote: Bulat Ziganshin wrote: people, are you know haskell apps that has more than 50k downloads per month (or more than 25k users) ? Possible candidates: * GHC * XMonad * Darcs * Pandoc I have no idea how to measure number of downloads or users, but pandoc is

Re: [Haskell-cafe] Haskell is a scripting language inspired by Python.

2010-11-05 Thread Tillmann Rendel
Hi, Albert Y. C. Lai wrote: I also invite you to play with my: http://www.vex.net/~trebla/humour/lmcify.html http://www.vex.net/~trebla/humour/lmcify.html?t=this+is+not+an+authorative+source. Tillmann ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Rigid types fun

2010-11-05 Thread Tillmann Rendel
Hi, Mitar wrote: I would like to do that to remove repeating code like: from- newChan for- newChan let nerve = Nerve (Axon from) (AxonAny for) which I have to write again and again just to make types work out. Why I cannot move that into the function? One option is to write a little library

Re: [Haskell-cafe] Edit Hackage

2010-10-31 Thread Tillmann Rendel
Ketil Malde wrote: Most web-based email archives seem to suck - where can we point to a nice URL to get an overview of a -cafe thread? http://thread.gmane.org/gmane.comp.lang.haskell.cafe/82667 Tillmann ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Red links in the new haskell theme

2010-10-30 Thread Tillmann Rendel
Henning Thielemann wrote: If I enable JavaScript in Konqueror, I still see no style menu. However I would like to get it without JavaScript. It can certainly be achieved using a cookie. Both stylesheets are linked to from the text of the HTML files: link href=ocean.css rel=stylesheet

Re: [Haskell-cafe] Red links in the new haskell theme

2010-10-30 Thread Tillmann Rendel
Henning Thielemann wrote: Firefox uses this information to populate a menu (View | Stylesheet) with the following choices: - no style - Ocean - Classic No need for JavaScript or cookies. This would be optimal for me, if it would work this way. From the answers I understood that the style

Re: [Haskell-cafe] type class design

2010-10-29 Thread Tillmann Rendel
Hi, Uwe Schmidt wrote: In the standard Haskell classes we can find both cases, even within a single class. Eq with (==) as f and (/=) as g belongs to the 1. case Note that the case of (==) and (/=) is slightly different, because not only can (/=) be defined in terms (==), but also the other

Re: [Haskell-cafe] A new cabal odissey: cabal-1.8 breaking its own neck by updating its dependencies

2010-09-12 Thread Tillmann Rendel
Hi Paolo, Paolo Giarrusso wrote: - when recompiling a package with ABI changes, does cabal always update dependent packages? It never recompiles them. Recompilation should not be needed, because different versions of packages exports different symbols, so a package can never be linked

Re: [Haskell-cafe] A new cabal odissey: cabal-1.8 breaking its own neck by updating its dependencies

2010-09-12 Thread Tillmann Rendel
Hi Paolo, Paolo Giarrusso wrote: $ cabal install --dry cabal-install leksah-0.8.0.6 [... does not work ...] However, trying to install cabal-install and leksah separately works quite well. So do install them separately. cabal install p1 p2 is supposed to find a single consistent install

Re: [Haskell-cafe] A new cabal odissey: cabal-1.8 breaking its own neck by updating its dependencies

2010-09-12 Thread Tillmann Rendel
Hi Paolo, Paolo Giarrusso wrote: cabal install p1 p2 is supposed to find a single consistent install plan for p1 and p2 and the transitive dependencies of either of them. This is useful if you plan to use p1 and p2 in a single project. Ahah! Then it's a feature. The need for consistency stems

Re: [Haskell-cafe] On to applicative

2010-09-01 Thread Tillmann Rendel
michael rice wrote: Prelude Data.Either let m = Just 7 Prelude Data.Either :t m m :: Maybe Integer So to create a value of type (Maybe ...), you can use Just. Prelude Data.Either let l = 2:[] Prelude Data.Either :t l l :: [Integer] So to create a value of type [...], you can use (:) and

Re: [Haskell-cafe] Unix emulation

2010-08-22 Thread Tillmann Rendel
Felipe Lessa wrote: I take it that the problem is that libcurl is a C library with a Unix-like build system, and that is the problem that needs Cygwin, right? One needs a compiler and libraries on the one hand, and a bunch of command-line tools on the other hand. On Windows, MinGW provides

Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel
Ertugrul Soeylemez wrote: let (x, world1) = getLine world0 world2 = print (x+1) world1 If between 'getLine' and 'print' something was done by a concurrent thread, then that change to the world is captured by 'print'. But in a world passing interpretation of IO, print is supposed to be

Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel
Bulat Ziganshin wrote: But in a world passing interpretation of IO, print is supposed to be a pure Haskell function. So the value world2 can only depend on the values of print and world1, but not on the actions of some concurrent thread. the whole World includes any concurrent thread though ;)

Re: [Haskell-cafe] Re: philosophy of Haskell

2010-08-15 Thread Tillmann Rendel
Brandon S Allbery KF8NH wrote: I am confused by this discussion. I originally thought some time back that IO was about world passing, but in fact it's just handing off a baton to insure that a particular sequence of IO functions is executed in the specified sequence and not reordered. Nothing

Re: [Haskell-cafe] Re: A GHC error message puzzle

2010-08-14 Thread Tillmann Rendel
Simon Marlow wrote: Really hClose shouldn't complain about a finalized handle, I'll see if I can fix that. That sounds like a work-around to me, not a fix, because it would not fix more complicated exception handlers. I don't think there's a problem with more complicated exception handlers.

Re: [Haskell-cafe] Re: A GHC error message puzzle

2010-08-13 Thread Tillmann Rendel
Simon Marlow wrote: So what happens is this: - the recursive definition causes the main thread to block on itself (known as a black hole) - the program is deadlocked (no threads to run), so the runtime invokes the GC to see if any threads are unreachable - the GC finds that (a)

Re: [Haskell-cafe] universal quantification is to type instantiations as existential quantification is to what

2010-08-12 Thread Tillmann Rendel
Hi, to understand forall and exists in types, I find it helpful to look at the terms which have such types. Joshua Ball wrote: mapInt :: forall a. (Int - a) - [Int] - [a] I can instantiate that function over a type and get a beta-reduced version of the type mapInt [String] :: (Int -

Re: [Haskell-cafe] Re: A GHC error message puzzle

2010-08-12 Thread Tillmann Rendel
Hi, the reading is not needed to make it happen. main = writeFile output blackhole where blackhole = blackhole In fact, writing is not needed either. main = bracket (openFile output WriteMode) hClose (\hdl - blackhole `seq` return ()) blackhole = blackhole Note that

Re: [Haskell-cafe] Accepting and returning polyvariadic functions

2010-08-11 Thread Tillmann Rendel
Will Jones wrote: f :: Int - IO () f = undefined g :: Int - Int - IO () g = undefined h :: Int - Int - Int - IO () h = undefined vtuple f :: IO (Int - (Int, ())) vtuple g :: IO (Int - Int - (Int, (Int, ( I've tried to type vtuple using a type class; [...] I've thought about

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-08-11 Thread Tillmann Rendel
Dan Doel wrote: But, to get back to BASIC, or C, if the language you're extending is an empty language that does nothing, then remaining pure to it isn't interesting. I can't actually write significant portions of my program in such a language, so all I'm left with is the DSL, which doesn't

Re: [Haskell-cafe] Couple of questions about *let* within *do*

2010-08-10 Thread Tillmann Rendel
michael rice wrote: OK, then there's also an implicit *in* after the *let* in this code. If you want to understand let statements in terms of let ... in ... expressions, you can do the following transformation: do s1 s2 let x1 = e1 x2 = e2 s3 s4 becomes do

Re: [Haskell-cafe] Suggestions For An Intro To Monads Talk.

2010-08-04 Thread Tillmann Rendel
Hi, aditya siram wrote: For example in the beginning it was useful for me to think of monads (and typeclasses really) as approximating Java interfaces. Type classes are somewhat parallel to Java interfaces, but Monad is a *specific* type class, so it should be somewhat parallel to a

Re: [Haskell-cafe] can Haskell do everyting as we want?

2010-08-04 Thread Tillmann Rendel
Ivan Lazar Miljenovic wrote:: My understanding of tab-completion in IDEs for Java, etc. is that it just displayed every single possible class method for a particular object value, and then did some kind of matching based upon what you typed to narrow down the list, not that it was type-based.

Re: [Haskell-cafe] Laziness question

2010-07-31 Thread Tillmann Rendel
michael rice wrote: f x = length [head x] g x = length (tail x) Wouldn't both functions need to evaluate x to the same level, *thunk* : *thunk* to insure listhood? There is no need to insure listhood at run time, since Haskell is statically typed. Tillmann

Re: [Haskell-cafe] Can we come out of a monad?

2010-07-30 Thread Tillmann Rendel
C K Kashyap wrote: I am of the understanding that once you into a monad, you cant get out of it? That's not correct. There are many monads, including Maybe, [], IO, ... All of these monads provide operations (=), return and fail, and do notation implemented in terms of these functions, as

Re: [Haskell-cafe] Re: Can we come out of a monad?

2010-07-30 Thread Tillmann Rendel
Hi, I wrote: There is nothing special about monads! Kevin Jardine wrote: I've seen plenty of comments suggesting that monads are easy to understand, but for me they are not. My point was that monads are not a language feature whith special treatment of the compiler, but more like a design

Re: [Haskell-cafe] Re: lhs2TeX - lhs2TeX.fmt missing

2010-07-11 Thread Tillmann Rendel
Hi Ivan, (why are you answering off-list?) Ivan Miljenovic wrote: I was under the impression that with cweb, you can have one function definition split into two, with another completely different block of code in between them. I agree, that's something literate haskell can not do. (But it's

Re: [Haskell-cafe] use of modules to save typing

2010-07-08 Thread Tillmann Rendel
Michael Mossey wrote: incrCursor :: State PlayState () Additional question: what is proper terminology here? Proper terminology for monadic things is somewhat debated. incrCursor is a monad This is not true. incrCursor is a monadic type incrCursor is not a type, so this can't be

  1   2   3   >