Re: [Haskell-cafe] Lenses: Should I declare Getters?

2013-09-10 Thread David Menendez
On Tue, Sep 10, 2013 at 1:31 AM, Charlie Paul wrote: > I've been looking through Edward Kmett's lens library, and I'm a bit > befuddled about Getters. In my own code, why would I want to have something > be a Getter instead of a plain function? As far as I can see, a plain > function is simpler t

Re: [Haskell-cafe] Applicative is like an Arrow

2013-08-17 Thread David Menendez
On Sat, Aug 17, 2013 at 8:23 AM, Mathijs Kwik wrote: > damodar kulkarni writes: > > > Thanks for this nice analogy and explanation. This brings "monad > > transformers" to my mind. > > "without" monad transformers, the monads are bit crippled in their > > applicability (please correct me if I am

Re: [Haskell-cafe] Can not use ST monad with polymorphic function

2012-12-01 Thread David Menendez
On Thu, Nov 29, 2012 at 7:50 AM, Dmitry Kulagin wrote: > Thank you, MigMit! > > If I replace your type FoldSTVoid with: > data FoldMVoid = FoldMVoid {runFold :: Monad m => (Int -> m ()) -> m ()} > > then everything works magically with any monad! > That is exactly what I wanted, though I still do

Re: [Haskell-cafe] type variable in class instance

2012-09-11 Thread David Menendez
I'm not sure I understand On Tue, Sep 11, 2012 at 11:06 AM, Corentin Dupont wrote: > Yes. > That's fantastic! This GADT is the missing piece of my puzzle. I transformed > a bit your solution, polluting it with some classes instances and fleshing > the functions: > > data Player = Arrive | Leave

Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-22 Thread David Menendez
As I see it, there are four possibilities for a given version of dependency: 1. The version DOES work. The author (or some delegate) has compiled the package against this version and the resulting code is considered good. 2. The version SHOULD work. No one has tested against this version, but the

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

2012-06-17 Thread David Menendez
On Sun, Jun 17, 2012 at 2:26 AM, Tillmann Rendel wrote: > 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 computa

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

2012-06-16 Thread David Menendez
On Sat, Jun 16, 2012 at 3:57 AM, Tillmann Rendel wrote: > 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 us

Re: [Haskell-cafe] Monads, do and strictness

2012-01-21 Thread David Menendez
On Sat, Jan 21, 2012 at 1:45 PM, David Barbour wrote: > On Sat, Jan 21, 2012 at 10:08 AM, Roman Cheplyaka wrote: >> >> * David Barbour [2012-01-21 10:01:00-0800] >> > As noted, IO is not strict in the value x, only in the operation that >> > generates x. However, should you desire strictness in

Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 8:10 AM, Bas van Dijk wrote: > On 16 December 2011 16:26, Yves Parès wrote: >> "1) What about the First type? Do we {-# DEPRECATE #-} it?" >> >> Personnaly, I'm in favor of following the same logic than Int: >> Int itself is not a monoid. You have to be specific: it's eith

Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 12:37 PM, wren ng thornton wrote: > On 12/19/11 10:20 PM, David Menendez wrote: >> >> On Mon, Dec 19, 2011 at 6:37 PM, wren ng thornton >>  wrote: >>> >>> On 12/14/11 10:58 PM, Gregory Crosswhite wrote: >>>> >>>

Re: [Haskell-cafe] Alternative versus Monoid

2011-12-21 Thread David Menendez
On Wed, Dec 21, 2011 at 12:20 PM, Conor McBride wrote: > > On 21 Dec 2011, at 14:07, Erik Hesselink wrote: > >> On Wed, Dec 21, 2011 at 14:10, Bas van Dijk wrote: > > >>  The semantics of Maybe are >>> >>> >>> clear: it's failure-and-prioritized-choice. >> >> >> Are you sure? > > > Yes. > > >> T

Re: [Haskell-cafe] [Alternative] change some/many semantics

2011-12-19 Thread David Menendez
On Mon, Dec 19, 2011 at 6:37 PM, wren ng thornton wrote: > On 12/14/11 10:58 PM, Gregory Crosswhite wrote: >> >> Of course, this is not a simple change at all because it would have to >> be done in such a way as to respect the ordering of actions --- that >> is, we can't have each action executed

Re: [Haskell-cafe] ismzero operator possible without equal constraint

2011-12-03 Thread David Menendez
On Sat, Dec 3, 2011 at 3:55 PM, Antoine Latter wrote: > On Sat, Dec 3, 2011 at 10:55 AM, edgar klerks wrote: >> Hi list, >> >> I am using MonadSplit >> (from http://www.haskell.org/haskellwiki/New_monads/MonadSplit )  for a >> project and now I want to make a library out of it. This seems to be >

Re: [Haskell-cafe] Interpreter with Cont

2011-11-21 Thread David Menendez
On Mon, Nov 21, 2011 at 2:13 PM, Tim Baumgartner wrote: > Free Monads. It's amazing to be confronted again with notions I learned more > than ten years ago for groups. I have to admit that I'm probably not yet > prepared for a deeper understanding of this, but hopefully I will return to > it later

Re: [Haskell-cafe] Interpreter with Cont

2011-11-20 Thread David Menendez
On Sat, Nov 19, 2011 at 3:29 PM, Felipe Almeida Lessa wrote: > On Sat, Nov 19, 2011 at 6:08 PM, Tim Baumgartner > wrote: >> I have not yet gained a good understanding of the continuation monad, but I >> wonder if it could be used here. What would a clean solution look like? >> Perhaps there are o

Re: [Haskell-cafe] Data Flow Programming in FP

2011-06-21 Thread David Menendez
On Tue, Jun 21, 2011 at 12:14 PM, Edward Kmett wrote: > The essence of data flow programming describes how you can use comonads to > model the semantics of dataflow languages. > > One of the best stops from there is probably, Dave Menendez's response on > the Haskell mailing list back in 2005 summ

Re: [Haskell-cafe] Probably type checker error.

2011-06-20 Thread David Menendez
GHC 6.12 introduces MonoLocalBinds, which disables polymorphic values in let statements. Your original code works for me if I use -XNoMonoLocalBinds -XNoMonomorphismRestriction. On Mon, Jun 20, 2011 at 9:02 AM, Serguey Zefirov wrote: > The fact is that (Num a) context works and (ToWires a, Num a

Re: [Haskell-cafe] Type Constraints on Data Constructors

2011-06-08 Thread David Menendez
On Wed, Jun 8, 2011 at 3:15 PM, Malcolm Wallace wrote: > >> data Bar f a = Foo f => Bar {bar :: f a} > > The class context on the data constructor buys you nothing extra in terms of > expressivity in the language.  All it does is force you to repeat the context > on every function that uses the

Re: [Haskell-cafe] ArrowLoop and streamprocessors

2011-03-31 Thread David Menendez
On Thu, Mar 31, 2011 at 11:01 AM, Matthew Steele wrote: > On Mar 30, 2011, at 5:29 PM, Mathijs Kwik wrote: > >> So loop really doesn't seem to help here, but I couldn't find another >> way either to feed outputs back into the system. >> What I need is: >> Either A B ~> Either C B -> A ~> C >> >> D

Re: [Haskell-cafe] Defining subtraction for naturals

2011-03-17 Thread David Menendez
On Thu, Mar 17, 2011 at 2:35 PM, wren ng thornton wrote: > Another question on particulars. When dealing with natural numbers, we run > into the problem of defining subtraction. There are a few reasonable > definitions: > > (1) If the result would drop below zero then throw an overflow error; > >

Re: [Haskell-cafe] Merry monad mixup?

2011-01-28 Thread David Menendez
On Fri, Jan 28, 2011 at 2:20 PM, michael rice wrote: > > The first and third work, but not the second. Why? > > Michael > > == > > f :: String -> IO () > f s = do putStrLn s > > {- > g :: [String] -> IO () > g l = do s <- l > putStrLn s > -} > > {- > h :: [Int] -> [Int] > h l

Re: [Haskell-cafe] Set monad

2011-01-08 Thread David Menendez
On Sat, Jan 8, 2011 at 4:53 PM, Lennart Augustsson wrote: > It so happens that you can make a set data type that is a Monad, but it's > not exactly the best possible sets. There's also the infinite search monad, which allows you to search infinite sets in finite time, provided your queries meet s

Re: [Haskell-cafe] Generalizing catMaybes

2011-01-08 Thread David Menendez
On Sat, Jan 8, 2011 at 5:07 PM, Tony Morris wrote: > > Thanks guys for all the solutions. A slight correction below. > > On 09/01/11 03:54, David Menendez wrote: >> >> Naturally, if you also have pure and fmap, you also have a monad. > You have a pointed functor but no

Re: [Haskell-cafe] Generalizing catMaybes

2011-01-08 Thread David Menendez
On Sat, Jan 8, 2011 at 12:05 PM, Conor McBride wrote: > > On 8 Jan 2011, at 15:27, Henning Thielemann wrote: > >> >> On Sat, 8 Jan 2011, Conor McBride wrote: >> >>> On 8 Jan 2011, at 11:14, Henning Thielemann wrote: >>> For me, the solutions of Dave Menendez make most sense: Generalize Maybe

Re: [Haskell-cafe] Generalizing catMaybes

2011-01-07 Thread David Menendez
On Fri, Jan 7, 2011 at 9:56 PM, Tony Morris wrote: > >  I am wondering if it possible to generalise catMaybes: > > (Something f, SomethingElse t) => t (f a) -> t a > > I have being doing some gymnastics with Traversable and Foldable and a > couple of other things from category-extras to no avail.

Re: [Haskell-cafe] Intro to monad transformers

2010-12-26 Thread David Menendez
On Sun, Dec 26, 2010 at 2:00 PM, michael rice wrote: > instance Monad m => MonadPlus (MaybeT m) where > mzero = MaybeT $ return Nothing > mplus x y = MaybeT $ do maybe_value <- runMaybeT x > case maybe_value of > Nothing

Re: [Haskell-cafe] type class design

2010-12-21 Thread David Menendez
On Tue, Dec 21, 2010 at 4:30 AM, Jean-Marie Gaillourdet wrote: > Hi, > > sorry for answering to such an old thread. > > David Menendez writes: > >> On Fri, Oct 29, 2010 at 8:33 AM, Tillmann Rendel >> wrote: >>> Hi, >>> >>> Uwe Schmidt wro

Re: Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 10:00 PM, John Lask wrote: >> On Thu, Nov 11, 2010 at 8:16 PM, John Lask  wrote: >>> >>> consider "length" ... >>> >>> I have records with the attribute length, length can be given as an Int, >>> Double, Float or maybe as a constructed type "Length", length's use as a >>> r

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread David Menendez
On Thu, Nov 11, 2010 at 8:16 PM, John Lask wrote: > consider "length" ... > > I have records with the attribute length, length can be given as an Int, > Double, Float or maybe as a constructed type "Length", length's use as a > record selector would also clash with List.length. All these have the

Re: [Haskell-cafe] type class design

2010-10-29 Thread David Menendez
On Fri, Oct 29, 2010 at 8:33 AM, Tillmann Rendel wrote: > 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 differe

Re: [Haskell-cafe] Restricted type classes

2010-09-09 Thread David Menendez
On Thu, Sep 9, 2010 at 11:33 PM, wren ng thornton wrote: > On 9/9/10 1:04 AM, David Menendez wrote: >> >> Fascinating. I figured there might be a counter-example involving seq, >> but this is pretty subtle. >> >> In particular, would it be fair to say that in H

Re: [Haskell-cafe] Restricted type classes

2010-09-08 Thread David Menendez
On Wed, Sep 8, 2010 at 11:17 PM, wren ng thornton wrote: > On 9/7/10 4:21 AM, Daniel Fischer wrote: >> >> On Tuesday 07 September 2010 05:22:55, David Menendez wrote: >>> >>> In fact, I think *every* appropriately-typed function satisfies that >>>

Re: [Haskell-cafe] Restricted type classes

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 10:22 PM, wren ng thornton wrote: > On 9/6/10 1:33 PM, David Menendez wrote: >> >> For that matter, can you even describe what pure is intended to do >> without reference to<*>  or join? > > As already stated: fmap f . pure = pure . f That

Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 2:21 PM, Daniel Díaz wrote: > > El Lun, 6 de Septiembre de 2010, 7:50 pm, David Menendez escribió: >> Operators default to infixl 9 unless specified otherwise, >> so no infix declaration is needed. > > Why there is a default infix? Why it is 9?

Re: [Haskell-cafe] Operator precedence

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 1:37 PM, michael rice wrote: > > A "concrete" library? > > I'm playing around with Data.Bits. It has .&. and .|. which I assume are > functions > (rather than operators) because I don't see and infix statement for them. > Correct? .|. and .&. are operators because they ar

Re: [Haskell-cafe] Restricted type classes

2010-09-06 Thread David Menendez
On Mon, Sep 6, 2010 at 7:51 AM, John Lato wrote: > On Sun, Sep 5, 2010 at 7:18 PM, David Menendez wrote: >> >> On Sun, Sep 5, 2010 at 8:40 AM, John Lato wrote: >> > >> > >> > On Sat, Sep 4, 2010 at 12:34 PM, David Menendez >> > wrote: &g

Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread David Menendez
On Sun, Sep 5, 2010 at 8:47 AM, Ivan Lazar Miljenovic wrote: > I _can_ think of a data type that could conceivably be an instance of > Pointed but not Applicative: a BloomFilter (though there's not really > any point in having a BloomFilter with only one value that I can see, > but maybe someone c

Re: [Haskell-cafe] Restricted type classes

2010-09-05 Thread David Menendez
On Sun, Sep 5, 2010 at 8:40 AM, John Lato wrote: > > > On Sat, Sep 4, 2010 at 12:34 PM, David Menendez wrote: >> >> On Fri, Sep 3, 2010 at 8:23 AM, John Lato wrote: >> >> > +1 for using the proper constraints, and especially for bringing over >>

Re: [Haskell-cafe] On to applicative

2010-09-04 Thread David Menendez
On Sat, Sep 4, 2010 at 2:06 PM, michael rice wrote: > The two myAction functions below seem to be equivalent and, for this small > case, show an interesting economy of code, but being far from a Haskell > expert, I have to ask, is the first function as small (code wise) as it > could be? > > Mich

Re: [Haskell-cafe] Restricted type classes

2010-09-04 Thread David Menendez
On Fri, Sep 3, 2010 at 8:23 AM, John Lato wrote: > Do you have a kind * implementation of Foldable?  I'd be interested in > seeing it, because I was unable to create a usable implementation (based > upon the RMonad scheme) on my last attempt. I always figured it would look something like: class

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-04 Thread David Menendez
On Sat, Sep 4, 2010 at 11:07 AM, John Millikin wrote: > On Fri, Sep 3, 2010 at 23:02, David Menendez wrote: >> Yes, using foreign namespaces is one of the things recommended against >> when serving XHTML as text/html. This says nothing about documents >> following the recomm

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-03 Thread David Menendez
On Sat, Sep 4, 2010 at 1:31 AM, John Millikin wrote: > On Fri, Sep 3, 2010 at 20:39, Albert Y. C. Lai wrote: >> In theory, what does file extension matter? Media type is the dictator. The >> normative Section 5.1 permits the choice of application/xhtml+xml or >> text/html. While the latter entail

Re: [Haskell-cafe] ANNOUNCE: Haddock version 2.8.0

2010-09-03 Thread David Menendez
On Fri, Sep 3, 2010 at 12:40 AM, John Millikin wrote: > > Haddock is generating files with an .html extension, which causes > webservers to serve it using "text/html", the incorrect MIME-type. Secton 5.1 of the XHTML recommendation states: "XHTML Documents which follow the guidelines set forth in

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 9:16 PM, michael rice wrote: > This may be a dumb question, but here goes. > > Types Maybe, Either, List, are types and also instances of Functor (and > Monad). > > Assuming (->) is also a type, where can I find its type definition? > (->) is a built-in type. You could say

Re: [Haskell-cafe] On to applicative

2010-09-02 Thread David Menendez
On Thu, Sep 2, 2010 at 10:45 AM, michael rice wrote: > > Can you think of a situation for > > \x -> f x > or > \x y z -> x + ord y - head z > > that would require x (y z) to have their type(s) declared (ala Pascal), or > is it always > inferred by what appears to the right of "->"? > I think H

Re: [Haskell-cafe] Arrow transformers: how to make them wright?

2010-08-31 Thread David Menendez
On Tue, Aug 31, 2010 at 2:07 PM, Permjacov Evgeniy wrote: >  A Control.Arrow in base package introduces an arrow type, and ghc have > good support for arrow notation. Many things, avaible in monads, are > avaible in arrows as well. There is an arrows package, that introduces > some arrow classes :

Re: [Haskell-cafe] Re: String vs ByteString

2010-08-14 Thread David Menendez
On Fri, Aug 13, 2010 at 10:43 AM, Johan Tibell wrote: > > Here's a rule of thumb: If you have binary data, use Data.ByteString. If you > have text, use Data.Text. Those libraries have benchmarks and have been well > tuned by experienced Haskelleres and should be the fastest and most memory > compa

Re: [Haskell-cafe] Yet another monad transformer or silly usage of Either?

2010-07-25 Thread David Menendez
2010/7/25 Eugeny N Dzhurinsky : > Hello, everybody! > > I am trying to develop some sort of library, which supposed to sign into a WEB > service, then perform some requests with it. > > Initially I designed methods in the following way > > data DServError = InvalidCredentials | InvalidRequest | ...

Re: [Haskell-cafe] Design for 2010.2.x series Haskell Platform site

2010-07-18 Thread David Menendez
On Sat, Jul 17, 2010 at 2:10 PM, Don Stewart wrote: > andrewcoppin: >> Don Stewart wrote: >>> allbery: >>> > like to repeat one request: Please, please, please make it easier to > - Download older versions of HP. > - Find out which HP release contains what. > - Figure out what the

Re: [Haskell-cafe] Actually loading a Cabal package in GHCi

2010-07-11 Thread David Menendez
On Sun, Jul 11, 2010 at 3:25 PM, wrote: > > Prelude Haskore> :l Haskore > > : module `Haskore' is a package module > Failed, modules loaded: none. You need to use :m here. -- Dave Menendez ___ Haskell-Cafe mailing

Re: [Haskell-cafe] Template Haskell sees into abstract data types

2010-07-03 Thread David Menendez
On Sat, Jul 3, 2010 at 7:20 PM, Ivan Lazar Miljenovic wrote: > Serguey Zefirov writes: > I cannot directly create my own class instances for them because of that. But I found that I can write Template Haskell code that could do that - those data types could be reified just fine. >

Re: [Haskell-cafe] checking types with type families

2010-07-03 Thread David Menendez
On Sat, Jul 3, 2010 at 3:32 AM, Kevin Quick wrote: > On Wed, 23 Jun 2010 00:14:03 -0700, Simon Peyton-Jones > wrote: > >> I'm interested in situations where you think fundeps work and type >> families don't.  Reason: no one knows how to make fundeps work cleanly with >> local type constraints (su

Re: [Haskell-cafe] Associated types

2010-07-01 Thread David Menendez
On Thu, Jul 1, 2010 at 2:35 PM, Christopher Lane Hinson wrote: > On Thu, 1 Jul 2010, Christopher Lane Hinson wrote: > >> >>> Something like this should work: >>> >>> class (Path p, CompletePath (CompletedPath p)) => IncompletePath p where >>>   type CompletedPath p :: * >>> >> >> AIUI, this isn't

Re: [Haskell-cafe] Associated types

2010-07-01 Thread David Menendez
On Thu, Jul 1, 2010 at 2:09 PM, Andrew Coppin wrote: > Consider the following: > >  class Path p where ... > >  class Path p => CompletePath p where ... > >  class Path p => IncompletePath p where >   type CompletedPath p :: * > > Obviously, the idea is that CompletedPath Foo (where Foo is an > In

Re: [Haskell-cafe] Re: The mother of all functors/monads/categories

2010-06-27 Thread David Menendez
On Sun, Jun 27, 2010 at 1:26 PM, Sebastian Fischer wrote: > Hi Max, > > very interesting observations! > >> By the way, you can use this stuff to solve the restricted monad >> problem (e.g. make Set an instance of Monad). This is not that useful >> until we find out what the mother of all MonadPlu

Re: [Haskell-cafe] Fwd: signficant improvements to the containers package

2010-06-25 Thread David Menendez
On Fri, Jun 25, 2010 at 12:58 AM, Ivan Miljenovic wrote: > On 25 June 2010 14:41, David Menendez wrote: >> On Thu, Jun 24, 2010 at 3:08 AM, Ivan Miljenovic >> wrote: >>> As an aside, Alex Mason and I are discussing the possibility of taking >>> advantage of

Re: [Haskell-cafe] Fwd: signficant improvements to the containers package

2010-06-24 Thread David Menendez
On Thu, Jun 24, 2010 at 3:08 AM, Ivan Miljenovic wrote: > As an aside, Alex Mason and I are discussing the possibility of taking > advantage of AusHack *shameless plug* to write some kind of classes > for the different types of containers with a hierarchy.  I know about > ListLike, but there doesn

Re: [Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread David Menendez
On Mon, Jun 21, 2010 at 7:04 AM, Neil Brown wrote: > > Here's my speculation, based on glancing at the libraries involved: I > believe the reason for this may be the MonadCatchIO instance for ContT: > > === > instance MonadCatchIO m => MonadCatchIO (ContT r m) where >   m `catch` f = ContT $ \c ->

Re: [Haskell-cafe] Re: Different choice operations in a continuation monad

2010-06-18 Thread David Menendez
On Fri, Jun 18, 2010 at 12:44 PM, Heinrich Apfelmus wrote: > Sebastian Fischer wrote: >> Edward Kmett wrote: >>> Sebastian Fischer wrote: Heinrich Apfelmus wrote: newtype CMaybe a = CMaybe (forall r. (a -> Maybe r) -> Maybe r) >>> Yes, with this type `orElse` has the same type as `mplus`

[Haskell-cafe] Re: Proposal to solve Haskell's MPTC dilemma

2010-05-27 Thread David Menendez
On Thu, May 27, 2010 at 10:39 AM, Carlos Camarao wrote: > Isaac Dupree: >> Your proposal appears to allow /incoherent/ instance selection. >> This means that an expression can be well-typed in one module, and >> well-typed in another module, but have different semantics in the >> two modules.  For

Re: [Haskell-cafe] FW: Why does this Ord-class instance crash?

2010-05-21 Thread David Menendez
2010/5/21 R J : > Why does the following, trivial  code snippet below hang GHCi when I type > "Scalene > Failure", and what's the fix? An instance of Ord must declare compare or (<=). You only defined (<), so (>) is using the default definition. Here are the defaults: compare x y = if x == y

Re: [Haskell-cafe] Proposal to solve Haskell's MPTC dilemma

2010-05-21 Thread David Menendez
On Fri, May 21, 2010 at 3:56 AM, Max Bolingbroke wrote: > On 21 May 2010 01:58, Carlos Camarao wrote: >> But this type-correct program would become not typeable if >> instances such as the ones referred to before (by Daniel Fischer) > > I was thinking this through, and the situation is more compl

Re: [Haskell-cafe] Type of (>>= f) where f :: a -> m b

2010-05-10 Thread David Menendez
On Mon, May 10, 2010 at 5:51 AM, Milind Patil wrote: > For a function > > f ::  a -> m b > f = undefined > > I am having trouble understanding how the type of > > (>>= f) > > is > > (>>= f) :: m a -> m b > > where, by definition, type of (>>=) is > > (>>=) :: (Monad m) => m a -> (a -> m b) -> m b

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Sat, May 8, 2010 at 1:16 AM, Ivan Lazar Miljenovic wrote: > David Menendez writes: > >> On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic >>> Well, any time you have a do-block like this you're using failable >>> patterns: >>> >>>

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Sat, May 8, 2010 at 12:15 AM, Ivan Lazar Miljenovic wrote: > David Menendez writes: >> >> I wonder how often people rely on the use of fail in pattern matching. >> Could we get by without fail or unfailable patterns? >> >> ensureCons :: MonadPlus

Re: [Haskell-cafe] IO (Either a Error) question

2010-05-07 Thread David Menendez
On Fri, May 7, 2010 at 10:26 PM, John Meacham wrote: > On Fri, May 07, 2010 at 08:27:04PM -0400, Dan Doel wrote: >> Personally, I don't really understand why unfailable patterns were canned >> (they don't seem that complicated to me), so I'd vote to bring them back, and >> get rid of fail. But hin

Re: [Haskell-cafe] Rank-2 polymorphism and overloading

2010-04-29 Thread David Menendez
On Mon, Apr 26, 2010 at 2:55 PM, Thomas van Noort wrote: > On 26-4-2010 20:12, Daniel Fischer wrote: >> >> Am Montag 26 April 2010 19:52:23 schrieb Thomas van Noort: >>> >>> ... >> >> Yes, y's type is more general than the type required by f, hence y is an >> acceptable argument for f - even z ::

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-24 Thread David Menendez
On Sat, Apr 24, 2010 at 5:56 AM, Barak A. Pearlmutter wrote: >> Even deriving(Ord) only produces compare and relies on standard >> definitions for other methods. > > I don't think that's actually a problem.  Surely the IEEE Floating > Point types would give their own definitions of not just compar

Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread David Menendez
On Fri, Apr 23, 2010 at 10:11 PM, John Goerzen wrote: > Don Stewart wrote: >> >> Oh, the Platform has very strict standards about APIs, >> >> When a package may be added: >>    http://trac.haskell.org/haskell-platform/wiki/AddingPackages > > That looks like a very solid document.  Does it also app

[Haskell-cafe] Re: Move MonadIO to base

2010-04-18 Thread David Menendez
On Sun, Apr 18, 2010 at 5:02 PM, wren ng thornton wrote: > Heinrich Apfelmus wrote: >> >> Anders Kaseorg wrote: >>> >>> This concept can also be generalized to monad transformers: >>> >>> class MonadTrans t => MonadTransMorph t where >>>    morph :: Monad m => (forall b. (t m a -> m b) -> m b) ->

Re: [Haskell-cafe] Integers v ints

2010-04-02 Thread David Menendez
On Thu, Apr 1, 2010 at 5:27 AM, Jens Blanck wrote: > I was wondering if someone could give me some references to when and why the > choice was made to default integral numerical literals to Integer rather > than to Int in Haskell. Also, if you are aware of similar discussions in > other languages.

Re: [Haskell-cafe] GHC vs GCC

2010-03-27 Thread David Menendez
On Sat, Mar 27, 2010 at 1:45 PM, Tillmann Rendel wrote: > 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 o

Re: [Haskell-cafe] GHC vs GCC

2010-03-26 Thread David Menendez
On Sat, Mar 27, 2010 at 12:56 AM, Thomas DuBuisson wrote: >> Using bang patterns didn't help almost anything here. Using rem >> instead of mod made the time go from 45s to 40s. Now, using -fvia-C >> really helped (when I used rem but not using mod). It went down to >> 10s. > > Bang patterns should

Re: [Haskell-cafe] Why is it so different between 6.12.1 and 6.10.4_1 ?

2010-03-26 Thread David Menendez
On Fri, Mar 26, 2010 at 9:13 PM, Ivan Lazar Miljenovic wrote: > David Menendez writes: >> On Fri, Mar 26, 2010 at 8:59 PM, Ivan Lazar Miljenovic >> wrote: >>> Some definitions and exports got changed, so in 6.12 the (-> a) Monad >>> instance is exported

Re: [Haskell-cafe] Why is it so different between 6.12.1 and 6.10.4_1 ?

2010-03-26 Thread David Menendez
On Fri, Mar 26, 2010 at 8:59 PM, Ivan Lazar Miljenovic wrote: > zaxis writes: >> In 6.10.4_1 under freebsd >>> let f x y z = x + y + z >> *Money> :t f >> f :: (Num a) => a -> a -> a -> a >> >>> :t (>>=) . f >> (>>=) . f  :: (Monad ((->) a), Num a) => a -> ((a -> a) -> a -> b) -> a -> b >>> ((>>=)

Re: [Haskell-cafe] Why is it so different between 6.12.1 and 6.10.4_1 ?

2010-03-26 Thread David Menendez
On Fri, Mar 26, 2010 at 8:20 PM, zaxis wrote: > > In 6.12.1 under archlinux >>let f x y z = x + y + z >> :t f > f :: (Num a) => a -> a -> a -> a > >> :t (>>=) . f > (>>=) . f :: (Num a) => a -> ((a -> a) -> a -> b) -> a -> b >> ((>>=) . f) 1 (\f x -> f x) 2 > 5 > > In 6.10.4_1 under freebsd >> let

Re: [Haskell-cafe] ANN: data-category, restricted categories

2010-03-26 Thread David Menendez
On Fri, Mar 26, 2010 at 11:07 AM, Edward Kmett wrote: > > On Fri, Mar 26, 2010 at 11:04 AM, Edward Kmett wrote: >> >> -- as long as you're ignoring 'seq' >> terminateSeq :: a -> Unit >> terminateSeq a = a `seq` unit >> > > Er ignore that language about seq. a `seq` unit is either another bottom o

Re: [Haskell-cafe] Re: Occurs check error, help!

2010-03-21 Thread David Menendez
On Sun, Mar 21, 2010 at 11:31 PM, adamtheturtle wrote: > So I have the code > > shuffle :: Int -> [a] -> [a] > shuffle i [] = [] > shuffle i cards = (cards!!i) : shuffle (fst pair) (delete (cards!!i) cards) >    where pair = randomR (0, 51) (mkStdGen 42) > > and it doesn't work, am I missing somet

Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-05 Thread David Menendez
On Fri, Feb 5, 2010 at 3:39 PM, Ryan Ingram wrote: > On Fri, Feb 5, 2010 at 5:19 AM, Martijn van Steenbergen > wrote: >> Ryan Ingram wrote: >>> >>> Unfortunately, this makes things like  infinite_xs <- sequence (repeat arbitrary) >>> >>> no longer work, since the state never comes out t

Re: [Haskell-cafe] Re: Generating repeatable arbitrary values with QuickCheck 2

2010-02-02 Thread David Menendez
On Tue, Feb 2, 2010 at 1:48 PM, Ryan Ingram wrote: > Gen slightly breaks the monad laws: > >> arbitrary >>= return > is not the same as >> return () >>= const arbitrary > because each bind splits the generator, so you end up with a different > seed passed to arbitrary in these two cases. > > If th

Re: [Haskell-cafe] very strange utf8 problem

2010-02-01 Thread David Menendez
2010/2/1 Günther Schmidt : > Hi all, > > I know this sounds daft but I do have good reason to ask. > > Is it possible that GHC's core itself has a problem with a particular Umlaut > only? > > HDBC-ODBC won't read in data from an SQLite database as soon as it comes > accross a *lowercase* U-Umlaut (

Re: [Haskell-cafe] Capped lists and |append|

2010-01-09 Thread David Menendez
On Fri, Jan 8, 2010 at 6:38 PM, John Millikin wrote: > Earlier today I uploaded the capped-list package; I didn't think there > would be any interest, since it's a relatively trivial data structure, > but already there's been three emails and an IRC convo about it. > > In short, this is Heinrich A

Re: [Haskell-cafe] (liftM join .) . mapM

2009-12-29 Thread David Menendez
On Tue, Dec 29, 2009 at 12:24 PM, Stephen Tetley wrote: > oo is one of of a family of functions I use often to avoid > sectioning/composing mania. It's known to Raymond Smullyan fans as > 'blackbird', though I call it oo as a pun on Standard MLs o (which is > Haskells (.) of course). > > -- | Comp

Re: [Haskell-cafe] Parse do block problem

2009-12-21 Thread David Menendez
On Mon, Dec 21, 2009 at 11:14 PM, joeltt wrote: > > I'm trying to write my first Haskell program. The below is the first real > logic block I've tried to write, unfortunately I get a "The last statement > in a 'do' construct must be an expression" error when loading the method. > However, the loca

Re: [Haskell-cafe] "Rebox Package" or "To Hackage or not to Hackage"

2009-12-08 Thread David Menendez
On Tue, Dec 8, 2009 at 4:25 PM, Vitaliy Akimov wrote: > Hi John, > > I don't know if this is useful for you, but these are instances of > Cofunctor's comap. For example if we use TypeCompose package we have: > > rebox f = unFlip . cofmap f . Flip Alternately, rebox = flip (.) -- Dave Menendez

Re: [Haskell-cafe] What is the rank of a polymorphic type?

2009-12-06 Thread David Menendez
On Sun, Dec 6, 2009 at 8:39 AM, Dan Doel wrote: > Apologies for the double-reply... > > Your mail prompted me to finally get around to adding a mono/polytype system > to an interpreter I've been working on for pure type systems, to see what a > GHC-alike type system would look like. Here's what I

Re: [Haskell-cafe] Are there standard idioms for lazy, pure error handling?

2009-12-04 Thread David Menendez
On Fri, Dec 4, 2009 at 1:14 PM, Jason McCarty wrote: > wren ng thornton wrote: > >>     concat1 :: T a b -> (b -> T a b) -> T a b > > This could just as easily be > >  concat :: T a b -> (b -> T a c) -> T a c > > right? It's a little weird to call this concatenation, but I bet it > could come in h

Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-03 Thread David Menendez
On Wed, Dec 2, 2009 at 7:16 PM, Martijn van Steenbergen wrote: > So here's a totally wild idea Sjoerd and I came up with. > > What if newtypes were unwrapped implicitly? As several have suggested, this creates ambiguity. But it might be handy to have a way to declare a scope in which the newtype

Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-03 Thread David Menendez
On Thu, Dec 3, 2009 at 6:28 AM, Joachim Breitner wrote: > Hi, > > Am Donnerstag, den 03.12.2009, 11:13 + schrieb Matthew Pocock: >> Perhaps what you are looking for is a more powerful "defining" >> semantics? >> >> newtype MyFoo = Foo defining (Foo(..)) -- all class instances that Foo >> has a

Re: [Haskell-cafe] Optimization with Strings ?

2009-12-03 Thread David Menendez
On Thu, Dec 3, 2009 at 12:32 PM, Alec Berryman wrote: > Emmanuel CHANTREAU on 2009-12-03 13:03:02 +0100: > >> In my futur program, it use a lot of binary trees with strings (words) >> as leaf. There is just arround 1000 words and they will appear a lot of >> times. The program will possibly consum

Re: [Haskell-cafe] Existencial Types

2009-12-01 Thread David Menendez
On Tue, Dec 1, 2009 at 1:00 PM, rodrigo.bonifacio wrote: > Dear all, I wrote the following  types: > >> class Transformation t where >>  (<+>) :: t -> SPLModel  -> InstanceModel -> InstanceModel > >> data Configuration = forall t . Transformation t => Configuration >> (FeatureExpression, [t]) >> t

Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-01 Thread David Menendez
On Tue, Dec 1, 2009 at 5:29 AM, Heinrich Apfelmus wrote: > Duncan Coutts wrote: >> On Mon, 2009-11-30 at 06:08 +, Malcolm Wallace wrote: >>> However, if you really want to terminate the stream at >>> the first error, and to reflect this in the type, then I guess you can >>> define your own lis

Re: [Haskell-cafe] Mystery operator?

2009-11-30 Thread David Menendez
On Mon, Nov 30, 2009 at 2:01 PM, michael rice wrote: > > Hi all, > > A lot of things posted here I wasn't aware of. My original example involved > ~(x,y), so, > returning to that context, how would these two simple cases vary: > > add2 :: (Int,Int) -> Int > add2 (x,y) = x+y > > add2 :: (Int,Int)

Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread David Menendez
On Sun, Nov 29, 2009 at 8:37 AM, Duncan Coutts wrote: > On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote: > >> The problem with this solution is that it doesn't scale. If we have M >> packages providing types and N packages providing classes, then we >> nee

Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-26 Thread David Menendez
On Thu, Nov 26, 2009 at 3:47 PM, Antoine Latter wrote: > > Lets say I want to provide an alternate or additional library of monad > transformer data types. To make these types maximally useful, they > should implement the typeclasses in the mtl package and in the > monads-tf package. > > The only

Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread David Menendez
On Wed, Nov 25, 2009 at 11:02 AM, Neil Brown wrote: > David Menendez wrote: >> >> From what I can tell, insEdge inserts an edge between two nodes which >> are already in the graph. The code is calling insEdge on >> arbitrarily-labeled nodes, which may not exist in the

Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread David Menendez
On Wed, Nov 25, 2009 at 6:28 AM, Neil Brown wrote: > It looks like a bug to me.  Can you show an exact list of nodes and edges > that is causing mkGraph to fail?  Or is that what you have displayed, and I > can't parse it properly? >From what I can tell, insEdge inserts an edge between two nodes

Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-18 Thread David Menendez
On Wed, Nov 18, 2009 at 4:12 PM, Edward Kmett wrote: > > Qualified imports are some times problematic when you need to work with > classes from the module. You can't define a member of two instances from > different two modules that define classes with conflicting member names. > This can lead to

Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread David Menendez
On Tue, Nov 17, 2009 at 10:01 PM, Luke Palmer wrote: > filter even [0..]    -->    [0,2,4,6,8,...] > searchList even [0...]   -->   Just [0,2,4,6,8,...] > > searchList gives Nothing in exactly those cases that filter gives []. > They give _|_ in exactly the same situations.  searchList could well

Re: Re[Haskell-cafe] cursive to foldr

2009-11-17 Thread David Menendez
On Tue, Nov 17, 2009 at 6:31 PM, Ezra Lalonde wrote: > > Using the same basic structure you did, and foldr, I think below is the > simplest method: > > > import Data.Maybe > > searchList :: (a -> Bool) -> [a] -> Maybe [a] > searchList p xs = foldr (\x acc -> if p x then Just (

  1   2   3   4   >