Re: [Haskell-cafe] Using Cabal during development

2010-02-09 Thread Miguel Mitrofanov
With cabal-install, usually. Limestraël wrote: Cabal/cabal-install are good tools for distribution and installation, but I was wondering -- as I was starting to learn how to use Cabal -- how do usually Haskell developpers build their softwares (and especially medium or big libraries) while the

Re: [Haskell-cafe] lazy'foldl

2010-02-10 Thread Miguel Mitrofanov
For the reference: foldM is defined as foldM :: Monad m => (a -> b -> m a) -> a -> [b] -> ma foldM _ a [] = return a foldM f a (x:xs) = f a x >>= \fax -> foldM f fax xs Let's define foldM' f x xs = lazy'foldl f (Just x) xs We can check that foldM' satisfies the same equations as foldM: foldM'

Re: [Haskell-cafe] HDBC convert [SqlValue] without muchos boilerplate

2010-02-11 Thread Miguel Mitrofanov
The problem is, "fromSql x" doesn't know that type it should return. It's sure that it has to be of class "Convertible SqlValue", but nothing more. Could be String, or Int32, or something else. What if you just omit the "show" function? fromSql seems to be able to convert almost anything to St

Re: [Haskell-cafe] Undecidable instances with functional dependencies

2010-02-11 Thread Miguel Mitrofanov
-- {-# LANGUAGE FunctionalDependencies#-} -- {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} module Register where -- class Register a r | a -> r class Register a where type R a -- instance Register Int Int instance Register Int where type R Int = Int -- instance Regis

Re: [Haskell-cafe] do we need types?

2010-02-26 Thread Miguel Mitrofanov
I'd say we don't really need subclasses. I mean, what's the difference: class Eq a where (==) :: a -> a -> Bool instance Eq a => Eq (Maybe a) where Nothing == Nothing = True Just x == Just y = x == y _ == _ = False sort :: Eq a => [a] -> [a] or data Eq a = Eq {eq :: a -> a -> Bool} eqMayb

Re: [Haskell-cafe] do we need types?

2010-02-26 Thread Miguel Mitrofanov
s/subclasses/classes/ Sorry for the confusion. Miguel Mitrofanov wrote: I'd say we don't really need subclasses. I mean, what's the difference: class Eq a where (==) :: a -> a -> Bool instance Eq a => Eq (Maybe a) where Nothing == Nothing = True Just x == Just y =

Re: [Haskell-cafe] Lists of Existential DT

2010-02-28 Thread Miguel Mitrofanov
Sorry, no luck with that. But you can, probably, define some "customized comma": data DrawPair a b = DrawPair a b (<,>) :: a -> b -> DrawPair a b (<,>) = DrawPair instance (Drawable a, Drawable b) => Drawable (DrawPair a b) where ... drawMany :: Drawable a => Window -> a -> IO () ... drawMany wi

Re: [Haskell-cafe] type class constraints headache

2010-03-03 Thread Miguel Mitrofanov
Which "a" should it use for "methods"? On 4 Mar 2010, at 09:07, muneson wrote: When writing a command-line interface I ran into type class conflicts I don't understand. Could anyone explain why ghc 6.10.4 compiles this methods :: (Eq a) => [(String, a)] methods = [ ("method1", undefined )

Re: [Haskell-cafe] Cabal-install

2010-03-08 Thread Miguel Mitrofanov
MigMit:~ MigMit$ cabal --help This program is the command line interface to the Haskell Cabal infrastructure. See http://www.haskell.org/cabal/ for more information. ^ | + On 8 Mar 2010, at 19:51, Andrew Coppin wrote: OK, so apparent

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

2010-03-10 Thread Miguel Mitrofanov
Maybe it's just me, but I think composition chain is MUCH easier to read. When readning, I'd probably transform the last version to the previous one by hand, just to make it more comprehensible. Sebastian Fischer wrote: On Mar 10, 2010, at 8:47 AM, Ketil Malde wrote: I think it is better st

Re: [Haskell-cafe] FRP, arrows and loops

2010-04-02 Thread Miguel Mitrofanov
1) Haven't look closely, but your second ArrowLoop instance seems righter. The question really is the same as with MonadFix instances; you can always define an instance like this data M = ... -- whatever instance Monad M where ... instance MonadFix M where mfix f = mfix f >>= f ...but this gen

Re: [Haskell-cafe] Hackage accounts and real names

2010-04-05 Thread Miguel Mitrofanov
Out of curiosity: is there something wrong with my nickname "migmit"? I'm not gonna change it anyway. On 6 Apr 2010, at 09:52, Edward Z. Yang wrote: This is a pretty terrible reason, but I'm going to throw it out there: I like real names because they're much more aesthetically pleasing. In

Re: [Haskell-cafe] Re: Haskell.org re-design

2010-04-07 Thread Miguel Mitrofanov
Doesn't seem right. IMHO, the necessity of making windows NOT fullscreen is an indication of bad design. Thomas Davie wrote: On 7 Apr 2010, at 02:53, Ben Millwood wrote: On Wed, Apr 7, 2010 at 2:22 AM, Thomas Schilling wrote: I have set a maximum width on purpose so that it doesn't degrade

Re: [Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Miguel Mitrofanov
Well, what's the sum of an empty list? Seems naturally that it's 0, but why? Let's say that sum [] = x. If we take two lists, say, l1 = [1,2,3] and l2 = [4,5], then sum l1 + sum l2 = 6 + 9 = 15 = sum [1,2,3,4,5] = sum (l1 ++ l2) We expect it to be the case even if one of the lists is empty, so

Re: [Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Miguel Mitrofanov
Forgot about this one: Bjorn Buckwalter wrote: What got me thinking about this was the apparently incorrect intuition that 'and xs' would imply 'or xs'. No. See, "and" is very close to "for all", and "or" is similarly close to "exists". For example, the statement "all crows are black" means j

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

2010-05-01 Thread Miguel Mitrofanov
It's called "monad transformers" func1' :: Int -> EitherT Error IO String func1' n = EitherT $ func1 n func2' :: Int -> EitherT Error IO String func2' s = EitherT $ func2 n runCalc' :: Int -> EitherT Error IO [String] runCalc' param = func1' param >>= func2' runCalc :: Int -> IO (Either Error [St

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

2010-05-02 Thread Miguel Mitrofanov
ErrorT :: IO (Either Error String) -> ErrorT Error IO String I can think that can be written as ErrorT :: IO (Either Error String) -> ErrorT Error (IO String) Am I correct? No, you're not. Similar to function application, type application is also left-associative, so it can (but shouldn't)

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

2010-05-10 Thread Miguel Mitrofanov
(>>= f) is equivalent to (flip (>>=) f), not to ((>>=) f). You can try this with your own function this way: (&$^) :: (Monad m) => m a -> (a -> m b) -> m b (&$^) = undefined :t (&$^ f) Milind Patil wrote: For a function f :: a -> m b f = undefined I am having trouble understanding how the

Re: [Haskell-cafe] Intuitive function given type signature

2010-05-18 Thread Miguel Mitrofanov
On 19 May 2010, at 08:35, Ivan Miljenovic wrote: This looks suspiciously like homework... 2010/5/19 R J : What are some simple functions that would naturally have the following type signatures: f :: (Integer -> Integer) -> Integer I can only think of one solution to this but it doesn't gu

Re: [Haskell-cafe] Retrospective type-class extension

2010-05-20 Thread Miguel Mitrofanov
That won't be a great idea; if I just want my monad to be declared as one, I would have to write instance Functor MyMonad where fmap = ... instance Pointed MyMonad where pure = ... instance Applicative MyMonad where (<*>) = ... instance Monad MyMonad where join = ... Compare this with instance

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

2010-05-21 Thread Miguel Mitrofanov
From Prelude.hs: class (Eq a) => Ord a where compare :: a -> a -> Ordering (<), (<=), (>), (>=) :: a -> a -> Bool max, min :: a -> a -> a compare x y = if x == y then EQ -- NB: must be '<=' not '<' to validate the --

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

2010-06-17 Thread Miguel Mitrofanov
listFs = [f1, f2, f3] map ($ x) listFs -- same as [f1 x, f2 x, f3 x] f x y z = ... map (\x -> f x u v) xs On 17 Jun 2010, at 23:02, Martin Drautzburg wrote: Hello all The standard map function applies a single function to a list of arguments. But what if I want to apply a list of functions

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-20 Thread Miguel Mitrofanov
I disagree. First of all, UHC states explicitly that some features are not supported (and probably never would be). Secondly, it seems like almost nobody uses (n+k)-patterns, and when they are used, they make the code less readable; so it's good NOT to support them, in order to make programmers a

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-20 Thread Miguel Mitrofanov
Well, the problem is that every implementor does choose a subset of standart to implement. It's much worse in JavaScript - essential features working differently in Internet Explorer, Firefox, Opera, and Safari, and sometimes they even differ between versions; Web programmers still manage. (n+k

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-20 Thread Miguel Mitrofanov
l to be equally bad. On Mon, Apr 20, 2009 at 1:23 PM, Miguel Mitrofanov wrote: Well, the problem is that every implementor does choose a subset of standart to implement. It's much worse in JavaScript - essential features working differently in Internet Explorer, Firefox, Opera, and Safari, and

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-20 Thread Miguel Mitrofanov
On 21 Apr 2009, at 04:59, Richard O'Keefe wrote: On 20 Apr 2009, at 10:12 pm, Miguel Mitrofanov wrote: I disagree. First of all, UHC states explicitly that some features are not supported (and probably never would be). Secondly, it seems like almost nobody uses (n+k)-patterns, Ho

Re: [Haskell-cafe] Re: Cabal's default install location

2009-04-21 Thread Miguel Mitrofanov
$ cat .cabal/config ... root-cmd: sudo ... user-install: False ... On 21 Apr 2009, at 14:41, Achim Schneider wrote: Thomas Davie wrote: There seems to be an assumption amongst the community that a user's home directory is the most useful place for cabal to install to by default. A few peopl

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-22 Thread Miguel Mitrofanov
On 22 Apr 2009, at 13:07, Jon Fairbairn wrote: Miguel Mitrofanov writes: Well, the problem is that every implementor does choose a subset of standart to implement. That's what I'm complaining about. And that's exactly what you (or anybody else) can't do anything ab

Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-22 Thread Miguel Mitrofanov
On 22 Apr 2009, at 21:19, Jason Dusek wrote: 2009/04/22 Miguel Mitrofanov : It's arrogant and disrespectful on the part of the implementors to say that they know better than the committee what features should be part of the language. It's arrogant and disrespectful on the p

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-23 Thread Miguel Mitrofanov
On 23 Apr 2009, at 12:17, Thomas Davie wrote: On 23 Apr 2009, at 10:02, Matthijs Kooijman wrote: Some material I've read on typography -- can't find the reference now -- suggests ~65 is the best number of characters per line. The advice was, if your page is larger than that, you should make

Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-23 Thread Miguel Mitrofanov
On 23 Apr 2009, at 23:07, Claus Reinke wrote: *Main> :t rollDie ~>> (rollDie ~>> rollDie) rollDie ~>> (rollDie ~>> rollDie) :: Seed -> (Int, Seed) This is a function. How exactly do you want ghci to show it? When you figure that out, feel free to make an instance of Show for it. Just becaus

Re: [Haskell-cafe] compilation to C, not via-C

2009-04-24 Thread Miguel Mitrofanov
Have you considered using FFI? On 24 Apr 2009, at 20:36, Sam Martin wrote: Hi Everyone, It appears the GHC compiler (and other) compile Haskell *via-C* but not *to C*. I've never really understood why there isn't a C generation option, or why GDC ships with its own compulsory copy of gcc.

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Miguel Mitrofanov
ys "derive everything possible". Therefore, it seems pointless to move it to another line. On 24 Apr 2009, at 16:37, Loup Vaillant wrote: 2009/4/23 Miguel Mitrofanov : On 23 Apr 2009, at 12:17, Thomas Davie wrote: Haskell is a very horizontal language, and to limit our horizontal

Re: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Miguel Mitrofanov
On 25 Apr 2009, at 17:32, j.waldmann wrote: * with practically every modern IDE You mean, with Emacs? * indentation should be by fixed amounts (e.g. 4 spaces for each level) and not depend on lengths of identifiers (because you might later change them) Agreed. I always write code tha

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Miguel Mitrofanov
On 25 Apr 2009, at 18:34, Xiao-Yong Jin wrote: Miguel Mitrofanov writes: On 24 Apr 2009, at 16:37, Loup Vaillant wrote: 2009/4/23 Miguel Mitrofanov : On 23 Apr 2009, at 12:17, Thomas Davie wrote: Haskell is a very horizontal language, and to limit our horizontal space seems pretty

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Miguel Mitrofanov
On 25 Apr 2009, at 19:08, Felipe Lessa wrote: On Sat, Apr 25, 2009 at 10:34:05AM -0400, Xiao-Yong Jin wrote: You don't write lisp, do you? Or probably it is just me. But I would prefer to write the line as newtype MyCoolMonad = MyCoolMonad (FirstTransformer

Re: Is 78 characters still a good option? Was: [Haskell-cafe] breaking too long lines

2009-04-25 Thread Miguel Mitrofanov
On 25 Apr 2009, at 19:59, Felipe Lessa wrote: On Sat, Apr 25, 2009 at 07:38:59PM +0400, Miguel Mitrofanov wrote: Also, I don't mistake the transformers as different parameters because of the parenthesis You should really try Lisp. In my opinion, parenthesis are a kind of noise - too

Re: [Haskell-cafe] Haskell/JS -- better through typeclasses?

2009-04-25 Thread Miguel Mitrofanov
On 25 Apr 2009, at 21:53, Jason Dusek wrote: Many Haskell/JS bridges provide libraries for writing complete JavaScript programs in Haskell; some of them even include jQuery. However, my goals are more limited -- I'd like to be able to take a Haskell module and turn it into a JavaScript obj

Re: [Haskell-cafe] Type constraints and classes

2009-04-26 Thread Miguel Mitrofanov
{-# LANGUAGE MultiParamTypeClasses #-} class Returnable m a where ret :: a -> m a class Bindable m a b where bind :: m a -> (a -> m b) -> m b newtype MOAMonad r m a = MOAMonad ((a -> m r) -> m r) instance Monad (MOAMonad r m) where return x = MOAMonad $ ($ x) MOAMonad h >>= f = MOAMonad $

Re: [Haskell-cafe] calling a variable length parameter lambda expression

2009-05-05 Thread Miguel Mitrofanov
Short answer: that's impossible. Well, with some oleging it should be possible, but the very fact that you're trying to do something like this indicates that you're doing something wrong. Where did this list of parameters came from? May be, you can apply your function to them one at a time,

Re: [Haskell-cafe] Unfold fusion

2009-05-06 Thread Miguel Mitrofanov
On 6 May 2009, at 19:27, Adrian Neumann wrote: Hello, I'm trying to prove the unfold fusion law, as given in the chapter "Origami Programming" in "The Fun of Programming". unfold is defined like this: unfold p f g b = if p b then [] else (f b):unfold p f g (g b) And the law states: unf

Re: [Haskell-cafe] Reply to

2009-05-06 Thread Miguel Mitrofanov
Anyway, I can't see why we still use mailing lists when we have reddit, which has all the good parts of mailing lists (nested messages), while it also: Hmm, what's this reddit thing? *googles* Me too. Seems like this "reddit" thing is nothing but a mail list done wrong. I may be wrong, but

Re: Re[Haskell-cafe] commending "Design concepts in programming languages"

2009-05-07 Thread Miguel Mitrofanov
* in the Appendix on notation, he defines composition of functions the "wrong way around" (i.e., the Haskell way, (f.g)(x) = f(g(x)). Just to make sure I understand correctly: are you claiming that Haskell definition of composition is wrong? ___ Has

Re: [Haskell-cafe] IO help

2009-05-07 Thread Miguel Mitrofanov
I have a suggestion. Why don't you grab some introductory book on Haskell and learn Haskell syntax a little? applebiz89 wrote on 07.05.2009 13:46: I havent done much IO at all in haskell, only within the function itself. However I want to get the input from the interface for the function and h

Re: [Haskell-cafe] monad . comonad = id

2009-05-08 Thread Miguel Mitrofanov
I have a question regarding the connection between monads and comonads. I always thought of the comonad operations as being the inverse operations of the corresponding monad functions. That's not true. If this is the case I would like to know what the corresponding monad for the following com

Re: [Haskell-cafe] monad . comonad = id

2009-05-08 Thread Miguel Mitrofanov
Seems like I was wrong. It does satisfy comonad laws. Sorry. However, the "duality" of monads and comonads isn't that simple. A comonad is actually a monad itself, but in different category. It has nothing to do with inverse functions etc. Jan Christiansen wrote on 08.05.2009 14:47: Hi, I ha

Re: [Haskell-cafe] commending "Design concepts in programming languages"

2009-05-08 Thread Miguel Mitrofanov
j.waldmann wrote on 08.05.2009 17:39: Wow. This is really a bikeshed discussion. My post contained praise for the book, a critique of one of its design decisions (intermediate language not explicitely typed), and a syntactical remark. Guess what the discussion is about. (This is also known as

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

2009-05-09 Thread Miguel Mitrofanov
Types. (>>=) :: Monad m => m a -> (a -> m b) -> m b (1+) :: Num a => a -> a So, the typechecker deduces that 1) "a" is the same as "m b", and 2) "a" (and "m b", therefore) must be of class "Num" Now, Just 3 :: Num t => Maybe t and the typechecker learns from that that "m a" must be the sa

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

2009-05-09 Thread Miguel Mitrofanov
On 10 May 2009, at 00:30, Brandon S. Allbery KF8NH wrote: On May 9, 2009, at 15:31 , michael rice wrote: Prelude> Just 3 >>= (1+) That (a -> m b) in the middle is what's failing to typecheck. The error is a bit obtuse because ghci is trying hard to find a way to do what you want, so it

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

2009-05-10 Thread Miguel Mitrofanov
On 10 May 2009, at 04:00, Cory Knapp wrote: ... There have been 12 replies to this question, all of which say the same thing. Brandon's one was different. And incorrect, which shows that this question isn't completely obvious. I'm glad we're so happy to help, but does Just 3 >>= return

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

2009-05-10 Thread Miguel Mitrofanov
On 10 May 2009, at 09:24, Brandon S. Allbery KF8NH wrote: I can't tell where I'm making the mistake here. Frankly, I can't do it either, because I don't understand what you're talking about. It seems that you have some idea of how the typechecker works, which is very different from that

Re: [Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-12 Thread Miguel Mitrofanov
I think that it's not nice to export 200 declarations from a single module. On 12 May 2009, at 18:05, Maurício wrote: Hi, When we want to list which declarations are exported by a module we do: module Mod ( list of exports ) where ... Are there propositions to alternatives to that (I could

Re: [Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-13 Thread Miguel Mitrofanov
Neil Brown wrote on 13.05.2009 14:23: Leaving aside the arguments about 200 exports, even for 20 exports it would sometimes be cleaner to write the above to hide one, than to spell out the other 19 in an export list. Note that Haddock orders exports according to the export list, not to an or

Re: [Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Miguel Mitrofanov
What would you expect foo [id, \x -> x] to be? Martin Hofmann wrote on 15.05.2009 12:09: It is pretty clear, that the following is not a valid Haskell pattern: foo (x:x:xs) = x:xs My questions is _why_ this is not allowed. IMHO, the semantics should be clear: The pattern is expected to succe

Re: [Haskell-cafe] conflicting variable definitions in pattern

2009-05-15 Thread Miguel Mitrofanov
Conor McBride wrote on 15.05.2009 16:19: My guess is that if this feature were already in, few would be campaigning to remove it. You're probably right. For example, I'm not compaigning to remove multiple inheritance (from non-abstract classes) from C++. But I still think it's an ugly feat

Re: [Haskell-cafe] Haskell in 3 Slides

2009-05-18 Thread Miguel Mitrofanov
On 18 May 2009, at 20:29, Joe Fredette wrote: While an incredibly small font is a clever option, a more serious suggestion may be as follows. 3-4 slides imply 3-4 topics, so the question is what are the 3-4 biggest topics in haskell? I would think they would be: * Purity/Referential Tran

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-18 Thread Miguel Mitrofanov
On 19 May 2009, at 09:06, Ryan Ingram wrote: This is a common problem with trying to use do-notation; there are some cases where you can't make the object an instance of Monad. The same problem holds for Data.Set; you'd can write setBind :: Ord b => Set a -> (a -> Set b) -> Set b setBind m f

Re: [Haskell-cafe] Re: [Haskell] [ANN] Safe Lazy IO in Haskell

2009-05-19 Thread Miguel Mitrofanov
gt; C m r a and backwards. Jason Dusek wrote on 19.05.2009 10:23: 2009/05/18 Miguel Mitrofanov : On 19 May 2009, at 09:06, Ryan Ingram wrote: This is a common problem with trying to use do-notation; there are some cases where you can't make the object an instance of Monad. The same problem holds

Re: [Haskell-cafe] showing a user defined type

2009-05-19 Thread Miguel Mitrofanov
michael rice wrote on 19.05.2009 18:16: Cool! Is there *anything* Haskell *can't* do? Well, I haven't found a way to emulate polymorphics kinds yet, and I feel like I need them. Other than than - probably no. Michael --- On *Mon, 5/18/09, David Menendez //* wrote: From: David Men

Re: [Haskell-cafe] Pattern match question in HAXML code

2009-05-23 Thread Miguel Mitrofanov
On 24 May 2009, at 01:19, Max Cantor wrote: Going through the instances for HTypeable (http://www.haskell.org/HaXml/HaXml/src/Text/XML/HaXml/TypeMapping.html#toHType ) I saw the following instance for Either a b. My question is, why doesn't the pattern match in the where clause always fail?

Re: [Haskell-cafe] Bool as type class to serve EDSLs.

2009-05-27 Thread Miguel Mitrofanov
And I would certainly celebrate when "if b then x else y" expression becomes polymorphic in "b". Edsko de Vries wrote on 27.05.2009 17:33: +1. I agree completely, I've missed this often for exactly the same reasons. Edsko ___ Haskell-Cafe mailing l

Re: [Haskell-cafe] Template Haskell very wordy w/r/t Decs and Types

2009-05-27 Thread Miguel Mitrofanov
On 27 May 2009, at 23:38, Simon Peyton-Jones wrote: Folks Quite a few people have asked for splices in Template Haskell *types*, and I have finally gotten around to implementing them. So now you can write things like instance Binary $(blah blah) where ... or f :: $(wubble bu

Re: [Haskell-cafe] Missing a "Deriving"?

2009-05-30 Thread Miguel Mitrofanov
It's trying to 'Show' the 'c [Int]' type, but doesn't know which 'c' to use; so it's trying to find a generic instance, which doesn't exist. You can't fix this with 'deriving' or anything like this; instead, provide the type annotation like this: *Main> searchAll g 1 3 :: Maybe [Int] On 31

Re: [Haskell-cafe] Non Empty List?

2009-06-04 Thread Miguel Mitrofanov
data Container a = Container a [a] ? Or, maybe, you need something like zipper. On 5 Jun 2009, at 01:53, GüŸnther Schmidt wrote: Hi, I need to design a container data structure that by design cannot be empty and can hold n elements. Something like a non-empty list. I started with: data

Re: [Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread Miguel Mitrofanov
Do you really need a class? Maybe, a simple data type would do? So, instead of class MyMonad m where myVal1 :: m a myVal2 :: m a -> m [a] instance Monad m => MyMonad (MyMonadT m) where myVal1 = foo myVal2 = bar you can write (in your first package) something like data MyMonad m

Re: [Haskell-cafe] Monad transformer responsibilities

2009-06-05 Thread Miguel Mitrofanov
Miguel Mitrofanov wrote on 05.06.2009 16:53: myMonadT :: Monad m => MyMonad m Sorry, I've meant myMonadT :: Monad m => MyMonad (MyMonadT m) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Why are these record accesses ambiguous

2009-06-06 Thread Miguel Mitrofanov
Probably because you don't apply "x" to "xx" anywhere? On 6 Jun 2009, at 11:48, John Ky wrote: Hi Haskell Cafe, In the following code, I get an error saying Ambiguous occurrence `x'. Why can't Haskell work out which x to call based on the type of getA? Thanks -John #!/usr/bin/env runh

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-10 Thread Miguel Mitrofanov
"r <- randomRIO (1,10)" is NOT the source of error. Why do you think it is? ptrash wrote on 10.06.2009 15:55: Hi, I have tried on the console to write x <- randomRIO(1,10) :t x Everythings fine and the type of x is x :: Integer Now I have tried to write a Method which gives me a Number of r

Re: [Haskell-cafe] Lightweight type-level dependent programming in Haskell

2009-06-10 Thread Miguel Mitrofanov
I recently discovered an interesting way of closing typeclasses while playing with type-level peano naturals: class Nat n where caseNat :: forall r. n -> (n ~ Z => r) -> (forall p. (n ~ S p, Nat p) => p -> r) -> r I usually use this one: class Nat n where caseNat :: p Z -> (forall m. N

Re: [Haskell-cafe] I need a hint in list processing

2009-06-14 Thread Miguel Mitrofanov
ghci> map reverse $ foldM (\answer list -> [x:answer | x <- list, not $ x `elem` answer]) [] [[2,3], [1,2], [2,3,4], [1,2,3]] [[2,1,4,3],[3,1,4,2],[3,2,4,1]] On 14 Jun 2009, at 12:06, Fernan Bolando wrote: Hi all If I have a number of list example list1 = [2,3] list2 = [1,2] list3 = [2,3,4]

Re: Fwd: [Haskell-cafe] curious about sum

2009-06-15 Thread Miguel Mitrofanov
Again: what if somebody wants to answer to the original author privately? It's easier to just use "Reply" for private answers and "Reply all" for list answers. Thomas ten Cate wrote on 15.06.2009 11:18: > On Sun, Jun 14, 2009 at 21:23, Jochem Berndsen wrote: >> Alberto G. Corona wrote: >>> Once m

[Haskell-cafe] Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
Hi! Suppose I want to create a specific monad as a combination of monad transformers - something like "StateT smth1 (ReaderT smth2 Identity)". As you can see, each transformer is parametrized with a type of kind *. I want to abstract these parameters, so that instead of "StateT smth..." I can w

Re: [Haskell-cafe] Documentation on hackage

2009-06-15 Thread Miguel Mitrofanov
But some of us would definitely find it amusing. Deniz Dogan wrote on 15.06.2009 16:53: 2009/6/15 minh thu : 2009/6/15 Uwe Schmidt : Dear Haskellers, who needs this kind of documentation? http://hackage.haskell.org/packages/archive/tfp/0.2/doc/html/Types-Data-Num-Decimal-Literals.html isn't

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
there are some more sophisticated methods like higher-level monad - but it seems almost impossible to abstract a class that can have an associated data type. I don't see any reason to do this - yet; and for me, "yet" is enough to make me nervous. On 16 Jun 2009, at 01:25, Ashley

Re: [Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
And the third one I forgot at first: so far, all code I wrote could be easily ported to Hugs. On 16 Jun 2009, at 02:00, Miguel Mitrofanov wrote: Probably. I have two objections against using type families. Both are pretty much theoretical. First, it seems to me that using type families

[Haskell-cafe] Re: Parametrized monads

2009-06-15 Thread Miguel Mitrofanov
What do you mean, without instances? How do you call "data instance" declarations? On 16 Jun 2009, at 02:16, Ashley Yakeley wrote: Miguel Mitrofanov wrote: First, it seems to me that using type families would require some other extensions. Multi-parameter type classes are OK,

Re: [Haskell-cafe] Tree Semantics and efficiency

2009-06-17 Thread Miguel Mitrofanov
You can use the standart "tying the knot"-technique. For example: data Tree = TreeNode String (Maybe Tree) [Tree] -- what's the parent of the root node? test :: Tree test = let parent = TreeNode "I'm parent" Nothing [child1, child2] child1 = TreeNode "I'm child1" (Just parent) []

Re: [Haskell-cafe] About the Monad Transformers

2009-06-17 Thread Miguel Mitrofanov
On 17 Jun 2009, at 19:54, .shawn wrote: Why does the type signature of mapTreeM look like this? Why not? I can't think of any other possibility. And what does it mean by "The lift tell us that we're going to be executing a command in an enclosed monad. In this case the enclosed monad is

Re: [Haskell-cafe] Re: Need some help with an infinite list

2009-06-20 Thread Miguel Mitrofanov
Well, I'm hardly the one knowing GHC internals, but... In allstrings you continue calling "strings" with same arguments again and again. Don't fool yourself, it's not going to automagically memorize what you were doing before. In fact, I'd expect much more speed loss. If you increase your "

Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Miguel Mitrofanov
An answer would probably depend on the reductions order you've chosen. Would that do? (\e -> e (\u -> e (\v -> u))) (\f -> \x -> f x) -- all variables have different names, see? = (\f -> \x -> f x) (\u -> (\f -> \x -> f x) (\v -> u)) = \x -> (\u -> (\f -> \x -> f x) (\v -> u)) x = \x -> (

Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Miguel Mitrofanov
Correction: I think that one can find an expression that causes name clashes anyway, I'm just not certain that there is one that would clash independent of whichever order you choose. On 21 Jun 2009, at 21:12, Miguel Mitrofanov wrote: An answer would probably depend on the reductions

Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Miguel Mitrofanov
Wow. Now you've showed it to me, it seems pretty obvious. That's what I like about math. On 21 Jun 2009, at 21:56, Bertram Felgenhauer wrote: Miguel Mitrofanov wrote: Correction: I think that one can find an expression that causes name clashes anyway, I'm just not certain th

Re: [Haskell-cafe] Slightly off-topic: Lambda calculus

2009-06-21 Thread Miguel Mitrofanov
Probably the easiest way to fix this was already proposed by Deniz Dogan: de Bruijn indices. On 21 Jun 2009, at 21:57, Andrew Coppin wrote: Lauri Alanko wrote: With "name collisions" I'm assuming you mean inadvertent variable capture. The answer depends on your evaluation strategy. If you ne

Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Miguel Mitrofanov
I so don't want to be the one supporting your code... Jules Bean wrote on 22.06.2009 13:00: Magnus Therning wrote: Also from experience, I get a good feeling about software that compiles without warnings. It suggests the author cares and is indicative of some level of quality. In contrast,

Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Miguel Mitrofanov
Jules Bean wrote on 22.06.2009 13:09: Miguel Mitrofanov wrote: I so don't want to be the one supporting your code... Well, that's lucky. Because you aren't. Exactly. However, that's an easy arrow to fling. I say I don't find warnings useful so you suggest my c

Re: [Haskell-cafe] ICFP contest

2009-06-23 Thread Miguel Mitrofanov
Well, I can make a bit more concrete prediction. I'll download the problem, take a look, try for a while, discover, that it's too hard to be cracked at once, and lose interest. That sounds like a reason why I'm not participating. On 23 Jun 2009, at 22:49, Rafael Gustavo da Cunha Pereira Pint

Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov
Well, without "fail" part: newtype IOMayfail a = IOMayfail (MaybeT IO a) deriving Monad Matthias Görgens wrote on 25.06.2009 17:14: By the way, how would one write the following with Monad Transformers? newtype IOMayfail a = IOMayfail (IO (Maybe a)) instance Monad IOMayfail where retur

Re: [Haskell-cafe] combining monads with IO

2009-06-25 Thread Miguel Mitrofanov
Sure: newtype IOMayfail a = IOMayfail {runIOMayfail :: MaybeT IO a} instance Monad IOMayfail where return = IOMayfail . return IOMayfail m >>= f = IOMayfail $ m >>= runIOMayfail . f fail = whatever you like Matthias Görgens wrote on 25.06.2009 17:28: Thanks. Can I add something like fai

Re: [Haskell-cafe] Reflections on the ICFP 2009 programming contest

2009-06-29 Thread Miguel Mitrofanov
I was excited when I read about the VM - I'd imagined all sorts of cool things, like assembler, linker, compiler (for something C-like), maybe even debugger... And what a disappointment it was when I understood that nothing of this kind is needed. On 29 Jun 2009, at 22:55, John Meacham wrot

Re: [Haskell-cafe] Reflections on the ICFP 2009 programming contest

2009-06-29 Thread Miguel Mitrofanov
On 30 Jun 2009, at 00:03, John Meacham wrote: The fact it didn't have any looping meant that it wasn't even fully turing complete and you probably couldn't speed it up much anyway, it already had an intrinsically short running time. Exactly! That's an ideal situation, you don't have to sp

Re: [Haskell-cafe] Problems with nested Monads

2009-07-10 Thread Miguel Mitrofanov
You can do this if D -> M (N D) is a monad itself. I suggest you study monad transformers - may be it's what you really want. On 10 Jul 2009, at 19:34, Job Vranish wrote: I'm trying to make a function that uses another monadic function inside a preexisting monad, and I'm having trouble. Ba

Re: [Haskell-cafe] RE: Haskell as a first language?

2009-07-14 Thread Miguel Mitrofanov
I disagree. It was easy enough for me. OK, I do have some Category Theory background and it certainly helps a lot. Still, I think that for a beginner (without any experience with C or anything like that) Haskell would be relatively easy. It doesn't involve (at least at the start) an ugly notion

Re: [Haskell-cafe] What to say about Haskell?

2009-07-14 Thread Miguel Mitrofanov
Domain theory semantics, I guess. I know, that if I (or rather a younger copy of me, not knowing a thing about Haskell) would be one of your students, and you tell me that there is such a clean and nice semantics for what we are doing, I'd be excited. Patai Gergely wrote: Hello all, I was a

Re: [Haskell-cafe] Circular pure data structures?

2009-07-14 Thread Miguel Mitrofanov
Sufficient, but not good. Try zippers instead. On 15 Jul 2009, at 08:29, John Ky wrote: Hello, Actually, I wanted to be able to create a tree structure when I can navigate both leaf-ward and root-ward. I didn't actually care for equality. I think the tying the knot technique as mention

Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Miguel Mitrofanov
No. Most constructors are functions, e.g. Just :: a -> Maybe a - a function. On the other hand, Nothing :: Maybe a is a constructor, but not a function. Andrew Wagner wrote: Err, technically, aren't functions and constructors mutually exclusive? So if something is a function, it's, by definitio

Re: [Haskell-cafe] A voyage of undiscovery

2009-07-16 Thread Miguel Mitrofanov
Consider the following expression: (foo True, foo 'x') Is this expression well-typed? Astonishingly, the answer depends on where "foo" is defined. If "foo" is a local variable, then the above expression is guaranteed to be ill-typed. However, if we have (for example) That's not true: mai

Re: [Haskell-cafe] is closing a class this easy?

2009-07-17 Thread Miguel Mitrofanov
What is it for? Yes, you would know that only A and B are Public, but you have no way of telling that to the compiler. I usually prefer something like that: class Public x where blah :: ... isAB :: forall y. (A -> y) -> (B -> y) -> x -> y Both solutions, however, allow the user to declare som

Re: [Haskell-cafe] is closing a class this easy?

2009-07-17 Thread Miguel Mitrofanov
Oops... Sorry, wrong line. Should be isAB :: forall p. p A -> p B -> p x On 18 Jul 2009, at 10:51, Miguel Mitrofanov wrote: What is it for? Yes, you would know that only A and B are Public, but you have no way of telling that to the compiler. I usually prefer something like that:

Re: [Haskell-cafe] ANN: AC-Vector, AC-Colour and AC-EasyRaster-GTK

2009-07-18 Thread Miguel Mitrofanov
On 18 Jul 2009, at 13:26, Wolfgang Jeltsch wrote: Am Samstag, 18. Juli 2009 06:31 schrieben Sie: On Jul 18, 2009, at 2:35 AM, Wolfgang Jeltsch wrote: So I should upload a package with German identifiers to Hackage? Sure, why not? The fact that I can't read it is my loss, not your fault, a

Re: [Haskell-cafe] is closing a class this easy?

2009-07-19 Thread Miguel Mitrofanov
On 18 Jul 2009, at 16:49, Wolfgang Jeltsch wrote: Am Samstag, 18. Juli 2009 08:58 schrieb Miguel Mitrofanov: Oops... Sorry, wrong line. Should be isAB :: forall p. p A -> p B -> p x Is this a well-known approach for closing classes? I have an impression that this is kinda folklore.

  1   2   3   4   5   >