Re: [Haskell-cafe] more thoughts on "Finally tagless"

2010-03-09 Thread Tillmann Rendel
Tom Schrijvers wrote: Yeah, subject "Finally Tagless" again, sorry, I'm just not done with it yet. In Olegs haskell implementation he is using classes mainly to model the syntax and instances to use for evaluators / compilers to allow multiple interpretations. I wonder if it'd be possible to do

Re: [Haskell-cafe] more thoughts on "Finally tagless"

2010-03-10 Thread Tillmann Rendel
Martijn van Steenbergen wrote: Tom Schrijvers wrote: data EvalDict sem = EvalDict { val :: Int -> sem Int, add :: sem Int -> sem Int -> sem Int } An alternative option is to capture the structure in a GADT: data Eval a where Val :: Int -> Eval Int Add :: Eval Int -> Eval Int -> Eval Int

Re: [Haskell-cafe] First time haskell - parse error!

2010-03-10 Thread Tillmann Rendel
Ketil Malde wrote: Also, good names are harder than they sound: I don't think 'belowLimit' is a good name for 'takeWhile (<1)', for instance. I certainly couldn't guess what it was for without looking at the implementation, which kind of defeats the purpose of names for improving code clarit

Re: [Haskell-cafe] more thoughts on "Finally tagless"

2010-03-10 Thread Tillmann Rendel
Tom Schrijvers wrote: William Cook's Onward! essay is relevant here. He characterizes the difference between objects and abstract data types nicely: the latter allow binary methods that pattern match (to exploit the combined knowledge of the internals of two different values) whereas objects only

Re: [Haskell-cafe] Abstraction in data types

2010-03-18 Thread Tillmann Rendel
Darrin Chandler wrote: data Point = Cartesian (Cartesian_coord, Cartesian_coord) | Spherical (Latitude, Longitude) type Center = Point type Radius = Float data Shape = Circle Center Radius | Polygon [Point] This obviously stinks since a Polygon could c

Re: [Haskell-cafe] searching a function by providing examples of input/ouput pairs

2010-03-18 Thread Tillmann Rendel
Paul Brauner wrote: feature [...] to search function in the library by giving a list of pairs of inputs/ouputs. [...] But, piggibacking such a feature on top of hoogle would surely be more efficient: 1. infer types for arguments and outout 2. look for matching functions using google 3. te

Re: [Haskell-cafe] Sugar for function application

2010-03-24 Thread Tillmann Rendel
Brandon S. Allbery KF8NH wrote: On Mar 23, 2010, at 13:39 , Ertugrul Soeylemez wrote: layout-style syntactic sugar for function application. Here is an example of what it might look like: function $$ anArgument sin (x^2) anotherArgument f $ x + 3 Doesn'

Re: [Haskell-cafe] GHC vs GCC

2010-03-27 Thread Tillmann Rendel
Jan-Willem Maessen wrote: It's worth pointing out that there's a bit of bang-pattern mysticism going on in this conversation (which has not been uncommon of late!). A non-buggy strictness analyzer should expose the strictness of these functions without difficulty. Could the result of stric

Re: [Haskell-cafe] Re: building "encoding" on Windows?

2010-03-30 Thread Tillmann Rendel
Ivan Miljenovic wrote: The Haskell Platform is supposed to be a development environment... No-one ever said it was a _complete_ development environment and that you'd never need any other libraries, tools, etc. On http://hackage.haskell.org/platform/contents.html, someone wrote: The Haskell

Re: [Haskell-cafe] Simple game: a monad for each player

2010-04-13 Thread Tillmann Rendel
Yves Parès wrote: data Player m = Player { plName :: String, -- unique for each player plTurn :: GameGrid -> m Move -- called whenever the player must play } What I try to avoid is having every player running in IO monad. One could define the following players. human :: MonadIO

Re: [Haskell-cafe] Function to find a substring

2010-06-08 Thread Tillmann Rendel
Hi, R J wrote: What's an elegant definition of a Haskell function that takes two strings and returns "Nothing" in case the first string isn't a substring of the first, or "Just i", where i is the index number of the position within the first string where the second string begins? The naive alg

[Haskell-cafe] The Arrow class (was: Vague: Assembly line process)

2010-06-16 Thread Tillmann Rendel
Bas van Dijk wrote: data Iso (⇝) a b = Iso { ab ∷ a ⇝ b , ba ∷ b ⇝ a } type IsoFunc = Iso (→) instance Category (⇝) ⇒ Category (Iso (⇝)) where id = Iso id id Iso bc cb . Iso ab ba = Iso (bc . ab) (ba . cb) An 'Iso (⇝)' also _almost_ forms an

Re: [Haskell-cafe] Mapping a list of functions

2010-06-17 Thread Tillmann Rendel
Martin Drautzburg wrote: The standard map function applies a single function to a list of arguments. But what if I want to apply a list of functions to a single argument. So your list of arguments is actually a list of functions. But since functions are first-class values, that shouldn't be a

Re: Réf. : Re: [Haskell-cafe] GHCi and State

2010-06-25 Thread Tillmann Rendel
Hi Corentin, corentin.dup...@ext.mpsa.com schrieb: for GHCi, i will try an IORef. Too bad i allready coded it using "StateT GameState IO ()" extensively through the code ;) That shouldn't be a problem, you could switch back and forth in submitRule, approximately like this: startGame :: IO

Re: [Haskell-cafe] Huffman Codes in Haskell

2010-06-26 Thread Tillmann Rendel
John Lato wrote: How would you implement bfnum? (If you've already read the paper, what was your first answer?) My first idea was something similar to what is described in appendix A. However, after reading the paper, I wrote the following code: data Tree a = E | T a (Tree a) (Tree a)

Re: [Haskell-cafe] Computing a sorted list of products lazily

2009-04-17 Thread Tillmann Rendel
Jason Dagit wrote: A colleague of mine recently asked if I knew of a lazy way to solve the following problem: Given two sets of sorted floating point numbers, can we lazily generate a sorted list of the products from their Cartesian product? The algorithm should return the same result as: sortPr

Re: [Haskell-cafe] breaking too long lines

2009-04-20 Thread Tillmann Rendel
Christian Maeder wrote: I've nothing against long names, but one shouldn't try to put blocks to the right of them. This is very important from my point of view. Indention should not depend on identifier length. However, I make an exception to that rule sometimes for definitions which look lik

Re: [Haskell-cafe] CPS and the product function

2009-04-20 Thread Tillmann Rendel
michael rice wrote: I've been looking at CPS in Haskell and wondering how many multiplications the product function performs if it encounters a zero somewhere in the input list. Zero? Does anyone know the definition of the product function? You can use Hoogle [1] to search for product [2]. T

Re: [Haskell-cafe] Non-atomic "atoms" for type-level programming

2009-04-22 Thread Tillmann Rendel
Hi Claus, thanks for your elaborations. I'm still not convinced that a common name (e.g. TT :. Tr :. Tu :. Te) is a better interface than a common import (e.g. TypeLevel.Bool.True). In both cases, the authors of all modules have to actively collaborate, either to define common names, or to de

Re: [Haskell-cafe] WHNF versus HNF

2009-04-22 Thread Tillmann Rendel
Peter Verswyvelen wrote: The GHC documentation of seq says: Evaluates its first argument to head normal form, and then returns its second argument as the result. I think this should be "weak head normal form". I don't think you have any means to evaluate under a binder in Haskell. The weak i

Re: [Haskell-cafe] Re: Converting IO [XmlTree] to [XmlTree]

2009-04-27 Thread Tillmann Rendel
Achim Schneider wrote: In other words: 1) Explain Pointed 2) Explain Functor 3) Explain Applicative 4) Explain Monad Why Pointed first? Functor seems more useful and more basic. Tillmann ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http:

Re: [Haskell-cafe] Non-atomic "atoms" for type-level programming

2009-04-29 Thread Tillmann Rendel
Hi, Claus Reinke wrote: One remaining issue is whether this encoding can be modified to allow for multiple independent instantiations of 'LA', 'LB', and 'LC' above, each with their own type parameters, in the same program. Modules A and B can make their dependence on the ultimate client module

Re: [Haskell-cafe] Non-atomic "atoms" for type-level programming

2009-04-29 Thread Tillmann Rendel
Hi again, Tillmann Rendel wrote: {-# LANGUAGE TypeFamilies #-} module D (ok) where import A import B data D client = D client type family Label client type instance A.Label (D client) = D.Label client type instance B.Label (D client) = D.Label client ok

Re: [Haskell-cafe] Help from C libraries experts

2009-04-30 Thread Tillmann Rendel
Hi, Maurício wrote: My goal is to have a place where one can find reliable and comprehensive low-level bindings to foreign libraries, so that writing higher level bindings becomes an easier task. Like others, I think you should consider making this place not a single package, but a bunch of p

Re: [Haskell-cafe] Getting started - help

2009-04-30 Thread Tillmann Rendel
Hi, applebiz89 wrote: data Film = Film String String Int String with this as the data. testDatabase :: [Film] testDatabase = [("Casino Royale", "Martin Campbell",2006, "Garry, Dave, Zoe")] Try to compile this part of the program, to get a feeling for whether you are on the right track. I

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel
Hi, normally, one uses monads to express and combine computations in the same monad. However, you can convert between some monads, e.g. from Maybe to List: import Data.Maybe (maybeToList) > let m1 = Nothing > let m2 = [1] > let m3 = maybeToList m1 `mplus` m2 > let m1 = Just 1 >

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Tillmann Rendel
Claus Reinke wrote: mplus' :: MonadPlus m => Maybe a -> m a -> m a mplus' m l = maybeToMonad m `mplus` l maybeToMonad :: Monad m => Maybe a -> m a maybeToMonad = maybe (fail "Nothing") return In general, however, this operation can't be done. For example, how would you write: mplus' :: I

Re: [Haskell-cafe] applicative challenge

2009-05-04 Thread Tillmann Rendel
Thomas Hartman wrote: -- Can the function below be tweaked to quit on blank input, provisioned in the applicative style? No. Applicative on its own does not support to decide which action to take based on the result of some previous action. It is therefore not possible to look at the last lin

Re: [Haskell-cafe] Interesting Thread on OO Usefulness (scala mailing list)

2009-05-04 Thread Tillmann Rendel
Hi, Paolo Losi wrote: I'm following an interesting thread on the scala mailing list: http://www.nabble.com/-scala--usefulness-of-OOP-td23268250.html Martin Odersky advocates the OO features of the scala language proposing an interesting problem where the OO approach seams valuable. I would be

Re: [Haskell-cafe] List comprehension

2009-05-05 Thread Tillmann Rendel
Hi, applebiz89 wrote: > Hi, I think I need to use a list comprehension There is no need to use list comprehensions, there is always a way to express the same thing without them. In fact, list comprehensions are defined as syntactic shorthands for this other way. filmsInGivenYear :: Int -> [

Re: [Haskell-cafe] instance Monad (Except err)

2009-05-06 Thread Tillmann Rendel
Hi, Martijn van Steenbergen wrote: Mr. McBride and mr. Paterson define in their Applicative paper: data Except e a = OK a | Failed e instance Monoid e => Applicative (Except e) where ... Sometimes I'd still like to use >>= on Excepts but this "feels" wrong somehow, because it doesn't use mo

Re: [Haskell-cafe] haskell - main function

2009-05-09 Thread Tillmann Rendel
applebiz89 wrote: becomeFan :: Title -> fanName -> [Film] -> [Film] becomeFan _ _ [] = [] becomeFan Title fanName ((Film Title Director Year fan):xs) | filmName == title = (Film Title Director Year fanName:fan) : xs | otherwise = (Film Title Director Year fan) : becomeFan Title fanName

Re: [Haskell-cafe] Just 3 >>= (1+)?

2009-05-09 Thread Tillmann Rendel
michael rice wrote: Prelude> Just 3 >>= (1+) Let's check the types. Prelude> :t (>>=) (>>=) :: (Monad m) => m a -> (a -> m b) -> m b Prelude> :t Just 3 Just 3 :: (Num t) => Maybe t Prelude> :t (1 +) (1 +) :: (Num a) => a -> a Renaming the variables in the type of (1 +) gives:

Re: [Haskell-cafe] Just 3 >>= (1+)?

2009-05-10 Thread Tillmann Rendel
Hi Cory, Cory Knapp wrote: ... There have been 12 replies to this question, all of which say the same thing. I'm glad we're so happy to help, but does Just 3 >>= return . (+1) Need to be explained by 12 different people? maybe eleven others have already pointed that out by now, but as far

Re: [Haskell-cafe] Re: OT: Languages

2009-05-10 Thread Tillmann Rendel
wren ng thornton wrote: Indeed. The proliferation of compound words is noteworthy, but it's not generally considered an agglutinative language. From what (very little) German I know compounds tend to be restricted to nouns, as opposed to languages like Turkish, Japanese, Korean,... Yes, compo

Re: [Haskell-cafe] Haskell IO problem

2009-05-10 Thread Tillmann Rendel
Hi apple, applebiz89 wrote: // Say I have this as my data type and list of films data Film = Film String String Int [String] -- List of films testDatabase :: [Film] testDatabase = [(Film "Casino Royale" "Martin Campbell" 2006 ["Garry", "Dave", "Zoe"]) ] // with functions such as: becomeFan ::

Re: [Haskell-cafe] ok, someone check me on this (type unification from the (>>=)/fmap thread)

2009-05-10 Thread Tillmann Rendel
Hi, Brandon S. Allbery KF8NH wrote: I can't tell where I'm making the mistake here. I'm not sure, but I guess you are mixing up some names. Did you make sure that all type variables are distinct before starting to unify? ... must have already unified (a) and (b) ... Why should it unify a

Re: [Haskell-cafe] Fundep Curiosity

2009-05-12 Thread Tillmann Rendel
Christopher Lane Hinson wrote: I've noticed that a large majority of fundeps I see in other people's libraries are written: class C a b | b -> a Where the dependent parameter appears first in the MPTC. Is there a reason for this? AFAIK, there isn't any semantic significance to the order of

Re: [Haskell-cafe] Structural sharing in haskell data structures?

2009-05-12 Thread Tillmann Rendel
Hi, Andrew Wagner wrote: So I'm just curious, does GHC use structural sharing or something similar? Structural sharing is not a feature of implementations, but of libraries. Consider this example: -- a function to "change" the head of a list replaceHead y xs = y : tail xs -- a big l

Re: [Haskell-cafe] Main function error

2009-05-12 Thread Tillmann Rendel
applebiz89 wrote: I have compiled each function independently and they have compiled the only problem is the main function.. I keep getting the error 'films not defined' and I am not sure why Well, because it is not defined :) type Title = String type Director = String type Year = Int type F

Re: [Haskell-cafe] Re: Error message reform

2009-05-30 Thread Tillmann Rendel
wren ng thornton wrote: (Though it doesn't necessarily generalize to cover similar messages like: Prelude> :t (\x -> x) :: a -> b :1:7: Couldn't match expected type `b' against inferred type `a' `b' is a rigid type variable bound by the polymorphic type `foral

Re: [Haskell-cafe] Re: Non Empty List?

2009-06-04 Thread Tillmann Rendel
Hi Günther, GüŸnther Schmidt wrote: data Container a = Single a | Many a [a] but the problem above I need a data structure as in my example without the [] being possible to be empty. So lets write a variant of list which cannot be empty. A usual list is empty, or a head and a tail:

[Haskell-cafe] Re: Non Empty List?

2009-06-05 Thread Tillmann Rendel
Hi, please write to the whole list, not just me. There are a lot of people around who can help you. MH wrote: Rendel do you mind to explain to me how Container a = Many a (Container [a]) prevents user from creating an empty list? I did try the following: let a = Many "string" a :: Container [

Re: [Haskell-cafe] Roman to Decimal Algorithms

2009-06-07 Thread Tillmann Rendel
Hi Andrew, Andrew Savige wrote: > Noticing this, you can replace the 205558`mod`(ord c)`mod`7 magic formula with a function that returns a string index (index() in Perl and Python). I am sometimes overwhelmed by the quantity and richness of all the functions in the GHC Haskell libraries. Have

Re: [Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Tillmann Rendel
Hi Hector, Hector Guilarte wrote: 1) Since Haskell is Lazy, and my GCL program is being interpreted in Haskell then my GCL is Lazy too (I know is not as simple as that but believe me, somehow it is behaving lazy). The problem is that it can't be lazy (said to me by my teacher on monday). eval

Re: [Haskell-cafe] A Strict GCL Interpreter in Haskell

2009-07-02 Thread Tillmann Rendel
Hi Hector, Hector Guilarte wrote: I did that already, but it didn't work... Also, since this kind of error would be a run time error in my GCL Language, I don't want it to continue executing whenever an error is found, that's why I changed it back to just: evalExpr:: Expr -> Tabla -> Int Inst

Re: [Haskell-cafe] lifting restrictions on defining instances

2009-07-27 Thread Tillmann Rendel
wren ng thornton wrote: [1] In System F the capital-lambda binder is used for the term-level abstraction of passing type representations. So for example we have, id :: forall a. a -> a id = /\a. \(x::a). x Thus, the forall keyword is serving as the type-level abstraction. Perhaps this

Re: [Haskell-cafe] lifting restrictions on defining instances

2009-07-28 Thread Tillmann Rendel
wren ng thornton wrote: Thus, the forall keyword is serving as the type-level abstraction. What do you mean by "type-level abstraction" here? I mean an abstraction, as in a lambda-abstraction (aka a lambda-expression), at the type level. [...] I'm not sure I follow what you mean. I

Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Tillmann Rendel
Hello, Phlex wrote: changePlanetAge universe galaxy planet age = ...lots of code, returning a new universe And the same code for all functions updating any of the properties of my planet ... And the same code for all functions updating properties of a country on this planet... In functional

Re: [Haskell-cafe] What puts False before True?

2007-06-05 Thread Tillmann Rendel
Tony Finch wrote: > Another point worth noting is that the usual lambda calculus > representations of false and zero are equivalent. (However true > is not the same as one.) Looking at Church encoding, false = zero true = may be a point for false < true, but true = curry fst false = cu

Re: [Haskell-cafe] Re: Parsec problem

2007-06-06 Thread Tillmann Rendel
Neil Mitchell wrote: The code is at: http://www.cs.york.ac.uk/fp/darcs/hoogle/src/Hoogle/Query/Parser.hs My guess: names can never fail, so types is never tried, and eof fails. Tillmann ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://w

Re: [Haskell-cafe] Newbie Q: Monad 'fail' and 'error'

2007-06-06 Thread Tillmann Rendel
Dmitri O.Kondratiev wrote: Monad class contains declaration *fail* :: String -> m a and provides default implementation for 'fail' as: fail s = error s On the other hand Prelude defines: * error* :: String -> a which stops execution and displays an error message. Questions: 1) What value an

Re: [Haskell-cafe] I saw this... and thought of you

2007-06-06 Thread Tillmann Rendel
Andrew Coppin wrote: http://dis.4chan.org/read/prog/1180896798/ (It's been a while since I touched Java, and I must confess I can't even comprehend this code...) Look's like a bad done extension of the well-known function object pattern in oo design to allow currying. I would prefer the foll

Re: [Haskell-cafe] Collections

2007-06-20 Thread Tillmann Rendel
Andrew Coppin wrote: [...] type (a,b) [...] That's a rather special type; I haven't seen anything remotely like it in any other language. This type isn't that special in Haskell (apart from being syntax-sugared), it could be defined as data Pair a b = Pair a b The equivalent of this de

Re: [Haskell-cafe] Parsec question

2007-06-21 Thread Tillmann Rendel
Levi Stephen wrote: newtype Identifier = Identifier String newtype Literal = StringLiteral String -- to be extended later data Primary = PrimaryLiteral Literal | PrimaryIdentifier Identifier primary = do { i <- identifier; return $ PrimaryIdentifier i; } <|> do { l <- s

Re: [Haskell-cafe] Collections

2007-06-21 Thread Tillmann Rendel
Andrew Coppin wrote: I don't even understand that... :-S Ok, I'll try to explain it: I represent sets by their characteristic function, wich returns True for members of the set, and False for other values. type Set a = a -> Bool For example, the set of numbers containing only 42 is repre

Re: [Haskell-cafe] Re: Reinvention

2007-06-27 Thread Tillmann Rendel
Andrew Coppin wrote: But IIRC the Parsec library supports parsing of arbitrary tokens (although presumably they have to be in Eq?) so maybe I should revise that... They don't have be in Eq, because you supply your own token tests, using the token or tokenPrim functions. Tillmann _

Re: [Haskell-cafe] Fun with ByteStrings [was: A very edgy language]

2007-07-08 Thread Tillmann Rendel
Andrew Coppin wrote: Now, as I understand it, a ByteString is a kind of unboxed array (= big RAM savings + big CPU time savings for not building it + big GC savings for not processing millions of list nodes + better cache performance). Or at least, a *strict* ByteString is; I'm very very fuzzy

Re: [Haskell-cafe] A very nontrivial parser

2007-07-08 Thread Tillmann Rendel
Andrew Coppin wrote: Oh, I don't mind not knowing how rank-2 types are *implemented*. ;-) But it would be nice to know what they *are*... :-S (Thus far, they just seem to be some incomprehensible syntax that makes the compiler stop complaining. In particular, I have no idea what the differenc

Re: [Haskell-cafe] Evaluation of IO actions in record assignment

2007-07-09 Thread Tillmann Rendel
Adde wrote: signatureEntry <- xmlGetWidget xml castToEntry "signatureEntry" passwordEntry <- xmlGetWidget xml castToEntry "passwordEntry" repeatEntry <- xmlGetWidget xml castToEntry "repeatEntry" return UserPanel {userPanelSignatureEntry = signatureEntry, userPanelPasswordEntry

Re: [Haskell-cafe] Help with IO and randomR

2007-07-16 Thread Tillmann Rendel
tpdfs' >>> return) using either Control.Monad or Control.Arrow. I'm not sure your aproach is numerically correct. Let's assume range = (0, 1). The resulting number could be (0 + 0) `div` 2 = 0 (0 + 1) `div` 2 = 0 (1 + 0) `div`

Re: [Haskell-cafe] Is this haskelly enough?

2007-07-18 Thread Tillmann Rendel
x27; n f = map f . unfoldr (((not . null . fst) `guarding`) . splitAt n) guarding p x = guard (p x) >> return x If you want to decide in the mapped function how many elements to consume, you can use unfoldr directly. Tillmann Rendel ___ Haskel

Re: [Haskell-cafe] Speedy parsing

2007-07-19 Thread Tillmann Rendel
Re, Joseph (IT) wrote: At this point I'm out of ideas, so I was hoping someone could identify something stupid I've done (I'm still novice of FP in general, let alone for high performance) or direct me to a guide,website,paper,library, or some other form of help. Two ideas about your aproaches:

Re: Re : [Haskell-cafe] Indentation woes

2007-07-26 Thread Tillmann Rendel
Stefan O'Rear wrote: Out of curiousity, what do you find objectionable about (legal): function argument argument2 | guard = body | guard = body as compared to (currently illegal): function argument argument2 | guard = body | guard = body I see the vertical strokes as visually lining up, po

Re: [Haskell-cafe] Newbie question: "multi-methods" in Haskell

2007-08-06 Thread Tillmann Rendel
peterv schrieb: In de book Modern C++ design, Andrei Alexandrescu writes that Haskell supports “multi-methods” http://books.google.com/books?id=aJ1av7UFBPwC&pg=PA3&ots=YPiJ_nWi6Y&dq=moder n+C%2B%2B&sig=FWO6SVfIrgtCWifj9yYHj3bnplQ#PPA263,M1 Chapter 11, Page 263 of this books: The C++ virtual f

Re: [Haskell-cafe] Type classes: Missing language feature?

2007-08-07 Thread Tillmann Rendel
DavidA wrote: Now, what I'd like to do is have Lex and Glex, and any further monomial orderings I define later, automatically derive Show and Num instances from Monomial (because it seems like boilerplate to have to define Show and Num instances by hand). Something like the following (not valid

Re: [Haskell-cafe] mutually recursive types

2007-08-08 Thread Tillmann Rendel
Rodrigo wrote: type Scenario = (String, String, [Step]) type Step = (String, Scenario, String, String, String) Recursive types are not supported by type-declarations. use data declarations instead: data Scenario = Scenario String String [Step] data Step = Step String Scenario String Stri

Re: [Haskell-cafe] Newbie question (again!) about phantom types

2007-08-08 Thread Tillmann Rendel
peterv wrote: I’m having difficulty to understand what phantom types are good for. I read the wiki, and it says "this is useful if you want to increase the type-safety of your code", but the code below does not give a compiler error for the function test1, I get a runtime error, just like test2

Re: [Haskell-cafe] where to put handy functions?

2007-08-10 Thread Tillmann Rendel
Chad Scherrer wrote: extract :: [Int] -> [a] -> [a] [...] This behaves roughly as extract ns xs == map (xs !!) ns extract sounds like removing the elements to be extracted from the original list. I would therefore expect it's type signature to be extract :: [Int] -> [a] -> ([a], [a]) wi

Re: [Haskell-cafe] Explaining monads

2007-08-12 Thread Tillmann Rendel
Ronald Guida wrote: Here's a toy language, described by a regular expression: 0(10)*110 I want to read characters, one at a time, and eventually decide to "Accept" or "Reject" a string. Let me try to understand my options. * With a simple Arrow, I can create a fixed sequence of "read" opera

Re: [Haskell-cafe] Re: Explaining monads

2007-08-13 Thread Tillmann Rendel
David Roundy wrote: It's the *effect* of a monad, not the *side* effect. The type of >>= defines this dependency. And when you have a chain of dependencies, that is sometimes referred to as a sequence. True, it's not mystical, but it's still sequenced. How can a Haskell type define a data de

Re: [Haskell-cafe] Re: [Off topic] Proving an impossibility

2007-09-04 Thread Tillmann Rendel
Vimal wrote: Ah, yes, it is possible in this case, but you have used an extra variable. It is okay, but our professor doesnt want to put emphasis on Computability here (or maybe I dont realize it), but the point is: Are such programming constructs really necessary in a programming language? i.e.

Re: [Haskell-cafe] newbie optimization question

2007-10-28 Thread Tillmann Rendel
i = 1; i <= 1; i++) { int sum = 0; for (int j = 1; j < i; j++) if (i % j == 0) sum += i; if (sum == i) print(i); } Loops can be expressed with lazy lists in Haskell. Therefore, the presented Haskell program is perfectly equivalent to the &quo

Re: [Haskell-cafe] Searched for mdo on haskell.org. Found nothing.

2007-11-22 Thread Tillmann Rendel
Hi Andrew, Andrew Coppin wrote: In general, I find *most* search functions to be fairly unhelpful. Google is the shining exception to this rule; it almost always seems to figure out what you're after. I guess doing text searching is just a fundamentally difficult problem, and the guys at Goo

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

2007-12-05 Thread Tillmann Rendel
Andrew Coppin wrote: *thinks* Conjecture #1: All nontrivial properties of a computer program are undecidable in general. That is the well-known Rice's theorem. (A very handy one in exams about theoretical computer science, since you can smash so many questions with "follows from Rice").

Re: [Haskell-cafe] Hoogle works once more

2007-12-06 Thread Tillmann Rendel
Dougal Stanton wrote: Is there a way to search on module names? If I put in Data.Map then the one thing that doesn't come up is a link to the library page for Data.Map. That would be a really good short-cut. You can already search for unqualified module names: http://haskell.org/hoogle/?q=Ma

Re: [Haskell-cafe] Software Tools in Haskell

2007-12-12 Thread Tillmann Rendel
Hi Tommy, detab is one of the programs I do not like. I kept the "direct translation" approach up through that, but I think it really hides the simplicity there; detab copies its input to its output replacing tabs with 1-8 spaces, based on where the tab occurs in a line. The only interestin

Re: [Haskell-cafe] OOP'er with (hopefully) trivial questions.....

2007-12-18 Thread Tillmann Rendel
Felipe Lessa wrote: class Shape a where whatever class (Shape a, Shape b) => Intersectable a b where intersect :: a -> b -> Bool This looks nice at first sight, but is it usefull in practice? I can somehow express the type "any shape wich is intersectable with a given other shape

Re: [Haskell-cafe] Multiple statements with Where

2007-12-18 Thread Tillmann Rendel
insertjokehere wrote: --A parser for recognising binary operations parseBinaryOp :: String -> String -> [(Expr, Expr, String)] parseBinaryOp op str | (elem op binops) && (notElem '(' (snd bm)) && (notElem ')' (snd bm)) && (elem nstr!!1 binops) = [(EInt 1, EInt 1, "HERE!")] You want (el

Re: [Haskell-cafe] Knowledge

2007-12-20 Thread Tillmann Rendel
jlw501 wrote: I'm new to functional programming and Haskell and I love its expressive ability! I've been trying to formalize the following function for time. Given people and a piece of information, can all people know the same thing? Anyway, this is just a bit of fun... but can anyone help me re

Re: [Haskell-cafe] Class/Instance : what am I doing wrong in this example ?

2007-12-20 Thread Tillmann Rendel
david48 wrote: class Gadget g where fInit :: g -> a -> g data FString = FString !Int !String deriving Show instance Gadget FString where at this point fInit has this type: FString -> a -> FString fInit (FString n _) s = FString n (take n s) but your implementation has this type

Re: [Haskell-cafe] instance Monad Either?

2007-12-20 Thread Tillmann Rendel
Eric wrote: According to this Either is an instance of class Monad, but when I try to use the do notation I get a compiler error. What's going on? Try to import Control.Monad.Error to get a Monad instance for Eit

Re: [Haskell-cafe] Difference lists and ShowS (Was: The Worker/Wrapper Transformation)

2008-01-03 Thread Tillmann Rendel
Henning Thielemann wrote: Sometimes I believed that I understand this reason, but then again I do not understand. I see that left-associative (++) like in ((a0 ++ a1) ++ a2) ++ a3 would cause quadratic time. But (++) is right-associative and 'concat' is 'foldr'. They should not scan the leadin

Re: [Haskell-cafe] Problem with own written monad

2008-01-07 Thread Tillmann Rendel
Michael Roth wrote: while trying to learn the secrets of monads, I decided to write a simply monand for pure educational purpose. But it turned out that it isn't as easy as I thought... I circumnavigate quite a number of hurdles but now I reached a point where I'm at a loss. :-( data Sta

Re: [Haskell-cafe] Type Mismatch

2008-01-07 Thread Tillmann Rendel
Cetin Sert wrote: class Streamable a where to :: a -> Stream a The type of to looks wrong for me. a -> Stream a means to takes a single element into a stream of such elements, but you probably want to convert between different representations of streams of elements. toStream :: [a] -> St

Re: [Haskell-cafe] Trouble with function with two clauses

2008-01-09 Thread Tillmann Rendel
Fernando Rodriguez wrote: data ConsCell a = Nil | Cons a (ConsCell a) deriving Show head' Nil = Nothing head' (Cons a _) = Just a Works fine, however, what's wrong with the following function? head'' | Nil = Nothing | Cons a _ = Just a You cannot use | as a general shortcut in functio

Re: [Haskell-cafe] confusion about 'instance'....

2008-01-10 Thread Tillmann Rendel
Nicholls, Mark wrote: I only have 1 type. If I say "my name is mark" twice, it doesn't mean I belong to set of objects called Mark twice Typeclasses define not only sets of types, but a common interface for these types, too. An analogy would be to say: I have a name, and it is Marc.

Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-10 Thread Tillmann Rendel
[EMAIL PROTECTED] wrote: Although it could be argued that laziness is the cause of some very obscure bugs... Niko Example, PLEASE. Prelude> sum [1..100] *** Exception: stack overflow Prelude> Data.List.foldl' (+) 0 [1..100] 5050 Tillmann __

Re: [Haskell-cafe] Re: Why purely in haskell?

2008-01-10 Thread Tillmann Rendel
Achim Schneider wrote: [1..] == [1..] [some discussion about the nontermination of this expression] The essence of laziness is to do the least work necessary to cause the desired effect, which is to see that the set of natural numbers equals the set of natural numbers, which, axiomatically, is

Re: [Haskell-cafe] background question about IO monad

2008-02-06 Thread Tillmann Rendel
Uwe Hollerbach wrote: lispUTCTime [] = doIOAction (getClockTime) toS allErrs where toS val = String (calendarTimeToString (toUTCTime val)) here you use liftIO (hidden in doIOAction) to use an IO action (getClockTime) inside of a different monad wich contains IO at it's base. so your custom

Re: [Haskell-cafe] Inverting a Monad

2008-02-06 Thread Tillmann Rendel
Bas van Dijk wrote: The following obviously doesn't work: import Control.Monad.Error inv :: MonadError e m => m a -> m () inv m = (m >> fail "") `catchError` \_ -> (return ()) What about this? inv :: MonadError e m => m a -> m () inv m = join $ (m >> return mzero) `catchError` \_ -> return (

Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-08 Thread Tillmann Rendel
Dan Weston wrote: Meanwhile, here is a hand-rolled solution to order-preserving nubbing: > import Data.List(groupBy,sortBy,sort) > import Data.Maybe(listToMaybe) > > efficientNub :: (Ord a) => [a] -> [a] > efficientNub = flip zip [0..]-- carry along index > >>> sort

Re: [Haskell-cafe] zlib or digest package installation

2010-06-30 Thread Tillmann Rendel
Hi Daniel, Daniel Kahlenberg wrote: when installing pandoc package, which has digest somewhere in dependencies the usual cabal install stucks because zlib.h is missing [...] I had a similar or the same problem with digest and zlib.h two months ago, which I reported to the Haskell platform tr

Re: [Haskell-cafe] Criteria for determining if a recursive function can be implemented in constant memory

2010-07-05 Thread Tillmann Rendel
Hi Steffen, Steffen Schuldenzucker wrote: since a little discussion with my tutor I am wondering how the following problem can be solved and if it is decidable: Given the definition of a recursive function f in, say, haskell, determine if f can be implemented in O(1) memory. Constant functi

Re: [Haskell-cafe] Subtype polymorphism in Haskell

2010-07-05 Thread Tillmann Rendel
Simon Courtenage wrote: I am porting a C++ program to Haskell. My current task is to take a class hierarchy and produce something equivalent in Haskell, but I don't seem to be able to get a grip on how type classes and instances contribute to the solution. They probably do not contribute a

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 c

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] 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] 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 _

  1   2   3   >