[Haskell-cafe] Fwd: How to make this data type work?

2013-06-21 Thread Miguel Mitrofanov
Forgot to reply all, as usual. Пересылаемое сообщение 21.06.2013, 12:52, Miguel Mitrofanov miguelim...@yandex.ru: Actually, this is not the real error you should care about. Try removing FromJSON instance completely, and you'll get a lot more. And these are fundamental: you

Re: [Haskell-cafe] Stuck on design problem

2013-05-20 Thread Miguel Mitrofanov
:t runMemLog (runTransitionT $ demo 1) runMemLog (runTransitionT $ demo 1) :: MonadLog (MemLog a) () = Log a - ((), [Command ()]) That means, that foo, if you manage to compile it, would have type MonadLog (MemLog a) () = ((), [Command ()]). That means that in each call for foo it would be

Re: [Haskell-cafe] Overloading

2013-03-12 Thread Miguel Mitrofanov
12.03.2013, 02:53, Richard A. O'Keefe o...@cs.otago.ac.nz: On 12/03/2013, at 10:00 AM, MigMit wrote:  On Mar 12, 2013, at 12:44 AM, Richard A. O'Keefe o...@cs.otago.ac.nz wrote:  Prelude :type (+)  (+) :: Num a = a - a - a  The predefined (+) in Haskell requires its arguments and its

[Haskell-cafe] ANNOUNCE: plat

2012-10-31 Thread Miguel Mitrofanov
My current project at work has a web interface. Therefore I needed an HTML templating library. I've tried several and found them all unsatisfactory. Most of them generate Haskell code from templates (with Template Haskell or a separate utility), and I don't like metaprogramming; and recompiling

Re: [Haskell-cafe] foldl vs. foldr

2012-09-18 Thread Miguel Mitrofanov
Hi Jan! foldl always traverses the list to the end; in particular, if there is no end, it would hang forever (unless the compiler is smart enough to detect an infinite loop, in which case it can throw an error). On the other hand, if the first argument is lazy enough, foldr would stop before

[Haskell-cafe] Bug or feature?

2012-07-20 Thread Miguel Mitrofanov
Hi cafe! I'm a bit confused by the DefaultSignatures extension. It's unclear whether to consider the following an example of clever use of this extension, or an example of abuse of it: {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-#

[Haskell-cafe] Inheritance constraints

2012-06-07 Thread Miguel Mitrofanov
Hi cafe! The ConstraintKinds extension makes it possible to create classes of classes, like this: class F c where cfmap :: c f = (a - b) - f a - f b instance F Functor where cfmap = fmap instance F Monad where cfmap = liftM So, basically we are saying that c is a class that has some special

Re: [Haskell-cafe] Monad laws in presence of bottoms

2012-02-22 Thread Miguel Mitrofanov
22.02.2012, 11:20, wren ng thornton w...@freegeek.org: On 2/22/12 1:45 AM, Miguel Mitrofanov wrote:  However, there is no free ordering on:    { (a0,b) | b- B } \cup { (a,b0) | a- A }  What? By definition, since, a0= a and b0= b, we have (a0, b0)= (a0, b) and (a0, b0)= (a0, b0), so

Re: [Haskell-cafe] Monad laws in presence of bottoms

2012-02-21 Thread Miguel Mitrofanov
22.02.2012, 09:30, wren ng thornton w...@freegeek.org: On 2/21/12 11:27 AM, MigMit wrote:  Ehm... why exactly don't domain products form domains? One important property of domains[1] is that they have a unique bottom element. Given domains A and B, let us denote the domain product as:    

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

2011-12-27 Thread Miguel Mitrofanov
27.12.2011, 07:30, "Alexander Solla" alex.so...@gmail.com:And why exactly should we limit ourselves to some theory you happen to like?Because the question was about MY IDEAL.  You're right. I'm confusing two different threads. My apologies.But (_|_) IS a concrete value.Um, perhaps in denotational

Re: [Haskell-cafe] Existential question

2011-08-18 Thread Miguel Mitrofanov
Now, what we can do with kl1? We can feed it an integer, say 1, and obtain function f of the type s - (s,Bool) for an _unknown_ type s. Informally, that type is different from any concrete type. We can never find the Bool result produced by that function since we can never have any concrete

Re: [Haskell-cafe] Difference between class and instance contexts

2011-08-03 Thread Miguel Mitrofanov
Try :t (foo 2, moo 2) On 3 Aug 2011, at 23:31, Patrick Browne wrote: Below are examples of using the sub-class context at class level and at instance level. In this simple case they seem to give the same results In general, are there certain situations in which one or the other is

Re: [Haskell-cafe] Haskell and Databases

2011-07-01 Thread Miguel Mitrofanov
HTML emails considered harmful. On 1 Jul 2011, at 23:17, Jack Henahan wrote: 'Courier New, 18pt' considered harmful? On Jul 1, 2011, at 3:08 PM, Christopher Done wrote: On 1 July 2011 20:51, Yves P limestr...@gmail.com wrote: There is something that bothers me with that text, I can't

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

2011-06-20 Thread Miguel Mitrofanov
it works in 6.12 also), you'll see that the type of nextSum etc. is derived as Num a = a. On 20 Jun 2011, at 17:02, Serguey Zefirov wrote: The fact is that (Num a) context works and (ToWires a, Num a) context doesn't. At least in 6.12.1. This still looks to me like a bug. 2011/6/19 Miguel

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

2011-06-19 Thread Miguel Mitrofanov
Seems like let-generalization is at work here. Types of all values in the where section are inferred basically as if they are declared at the top level. Therefore, inheritance fails without NoMonomorphismRestriction. There is a proposal (from Big Simon) to remove let-generalization:

Re: [Haskell-cafe] naming convention for maybes?

2011-04-22 Thread Miguel Mitrofanov
Well, Maybe IS a monad, so I just use m prefix. Отправлено с iPhone Apr 22, 2011, в 21:14, Evan Laforge qdun...@gmail.com написал(а): Here's a simple issue that's been with me for a while. As do many people, I use plural variable names for lists, so if a Block as called 'block' then [Block]

Re: [Haskell-cafe] IO and Cont as monads

2011-04-12 Thread Miguel Mitrofanov
As for Cont, it can be proved easily, either by hand, or by observation that Cont is an obvious composition of two adjoint functors. As for IO, it has to be taken for granted, since IO internals are hidden from the programmer. Отправлено с iPhone Apr 12, 2011, в 14:39, Burak Ekici

Re: [Haskell-cafe] Type trickery

2011-03-16 Thread Miguel Mitrofanov
I fail to see how does it limit the scope. 16.03.2011 15:05, Andrew Coppin пишет: You could define a function: withContainer ∷ (∀ s. Container s → α) → α which creates a container, parameterizes it with an 's' that is only scoped over the continuation and applies the continuation to the

Re: [Haskell-cafe] FFI: C-side object not destructed

2011-02-26 Thread Miguel Mitrofanov
Well, this code in C++ would probably work too: Klass *k = new Klass(4,5); delete k; std::cout k-getY() std::endl; though smart compiler would probably issue a warning. See, when you delete something, C++ doesn't automagically mark your pointer as invalid; in fact, it preserves all the data

Re: [Haskell-cafe] Noob question about list comprehensions

2011-02-16 Thread Miguel Mitrofanov
length [c | x - [1..100], let c = chain x, length c 15] 16.02.2011 12:19, Tako Schotanus пишет: Hello, I was going through some of the tuturials and trying out different (syntactic) alternatives to the given solutions and I I got to this line: *length [chain x | x - [1..100] , length

Re: [Haskell-cafe] Haskell, C and Matrix Multiplication

2011-01-17 Thread Miguel Mitrofanov
Sorry, but last time I've checked, C did have loops, is that correct? And even if you don't want loops, there is a preprocessor. 17.01.2011 10:45, Blake Rain пишет: Dear Haskellers, I thought I'd take some time to share something of my weekend with you all. Not because of anything new,

Re: [Haskell-cafe] Why is Haskell flagging this?

2010-12-17 Thread Miguel Mitrofanov
On 17 Dec 2010, at 20:04, michael rice wrote: I don't understand this error message. Haskell appears not to understand that 1 is a Num. As it clearly states in the error message, it doesn't understand that [Int] is a Num - and it's not. No instance for Num something usually indicates that

Re: [Haskell-cafe] Avoiding the Y combinator for self-referencing types

2010-12-12 Thread Miguel Mitrofanov
Not sure if that's what you need: data NodeF f = Node {name :: String, refs :: [f (NodeF f)]} newtype Const a b = Const a newtype Id a = Id a type NodeS = NodeF (Const String) type Node = NodeF Id Отправлено с iPhone Dec 12, 2010, в 20:54, Florian Weimer f...@deneb.enyo.de написал(а):

Re: [Haskell-cafe] Test

2010-11-30 Thread Miguel Mitrofanov
Missed. On 30 Nov 2010, at 23:47, Ian Lynagh wrote: A1 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] version of findIndex that works with a monadic predicate

2010-11-26 Thread Miguel Mitrofanov
findIndexM = (liftM (findIndex id) .) . mapM On 26 Nov 2010, at 22:46, José Romildo Malaquias wrote: Hello. I need a function findIndexM, similar to findIndex from the standard module Data.List, but which works with a monadic predicate to test list elements. findIndex :: (a - Bool) -

Re: [Haskell-cafe] Derived type definition

2010-11-24 Thread Miguel Mitrofanov
family extension. I've tried ... without success. Thx. On 11/22/2010 10:46 PM, Miguel Mitrofanov wrote: Sure, it's possible with TypeFamilies. The following compiles OK: {-# LANGUAGE TypeFamilies #-} module TypeCalc where data Rec a r = Rec a r data RecNil = RecNil data Wrapper a = Wrapper

Re: [Haskell-cafe] Monadic function purity

2010-11-24 Thread Miguel Mitrofanov
Generally speaking, all Haskell functions are pure unless they use unsafe- functions or FFI inside. Отправлено с iPhone Nov 24, 2010, в 23:46, Gregory Propf gregorypr...@yahoo.com написал(а): I have a pretty basic question. I've been wondering about whether monadic functions that do NOT us

Re: [Haskell-cafe] Wondering if this could be done.

2010-11-22 Thread Miguel Mitrofanov
Sure, you can define your own type class like that: import Prelude hiding ((+), (-)) -- usual (+) and (-) shouldn't be here... import qualified Prelude as P -- but they still are accessible with a prefix class Group a where (+) :: a - a - a (-) :: a - a - a instance Group Integer where

Re: [Haskell-cafe] Derived type definition

2010-11-22 Thread Miguel Mitrofanov
Sure, it's possible with TypeFamilies. The following compiles OK: {-# LANGUAGE TypeFamilies #-} module TypeCalc where data Rec a r = Rec a r data RecNil = RecNil data Wrapper a = Wrapper a class TypeList t where type Wrapped t i :: t - Wrapped t instance TypeList RecNil where type

Re: [Haskell-cafe] About Fun with type functions example

2010-11-19 Thread Miguel Mitrofanov
A continuation. You can't know, what type your fromInt n should be, but you're not going to just leave it anyway, you're gonna do some calculations with it, resulting in something of type r. So, your calculation is gonna be of type (forall n. Nat n = n - r). So, if you imagine for a moment

Re: [Haskell-cafe] Type Directed Name Resolution

2010-11-11 Thread Miguel Mitrofanov
11.11.2010 16:53, Stephen Tetley пишет: On 11 November 2010 13:10, Lauri Alankol...@iki.fi wrote: {-# LANGUAGE EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies #-} data PetOwner data FurnitureOwner data Cat = Cat { catOwner :: PetOwner } data Chair = Chair { chairOwner ::

Re: [Haskell-cafe] http://functionalley.eu

2010-11-06 Thread Miguel Mitrofanov
Black letters over dark blue background hurt my eyes. On 6 Nov 2010, at 18:10, Alistair Ward wrote: I've just written a few packages which I think may be useful, and have made them available as free opensource on a personal website http://functionalley.eu. I opted to host them there rather

Re: [Haskell-cafe] What is simplest extension language to implement?

2010-11-02 Thread Miguel Mitrofanov
Ehm... Forth? TCL? Отправлено с iPhone Nov 2, 2010, в 9:04, Permjacov Evgeniy permea...@gmail.com написал(а): Let us think, that we need some scripting language for our pure haskell project and configure-compile-run is not a way. In such a case a reasonably simple, yet standartized and wide

Re: [Haskell-cafe] Proving stuff about IORefs

2010-10-17 Thread Miguel Mitrofanov
On 17 Oct 2010, at 05:21, Ben Franksen wrote: I want to prove that f r == do s1 - readIORef r r' - newIORef s1 x - f r' s3 - readIORef r' writeIORef r s3 return x That is not true. Consider the following function: g r1 r2 = writeIORef r1 0 writeIORef r2 1

Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Miguel Mitrofanov
hdList :: List a n - Maybe a hdList Nil = Nothing hdList (Cons a _) = Just a hd :: FiniteList a - Maybe a hd (FL as) = hdList as *Finite hd ones this hangs, so, my guess is that ones = _|_ 13.10.2010 12:13, Eugene Kirpichov пишет: {-# LANGUAGE ExistentialQuantification, GADTs,

Re: [Haskell-cafe] Finite but not fixed length...

2010-10-13 Thread Miguel Mitrofanov
So... you want your ones not to typecheck? Guess that's impossible, since it's nothing but fix application... 13.10.2010 12:33, Eugene Kirpichov пишет: Well, it's easy to make it so that lists are either finite or bottom, but it's not so easy to make infinite lists fail to typecheck... That's

Re: [Haskell-cafe] Re: Lambda-case / lambda-if

2010-10-07 Thread Miguel Mitrofanov
Отправлено с iPhone Oct 7, 2010, в 21:03, Peter Wortmann sc...@leeds.ac.uk написал(а): On Tue, 2010-10-05 at 17:10 -0700, Evan Laforge wrote: +1 for something to solve the dummy - m; case dummy of problem. Here are the possibilities I can think of: Might be off-topic here, but I have

Re: [Haskell-cafe] Simple question about the function composition operator

2010-09-24 Thread Miguel Mitrofanov
(g . f) x y = (\z - g (f z)) x y = g (f x) y, and you need g (f x y), which is definitely not the same thing. 24.09.2010 13:35, Axel Benz пишет: Hello, this is maybe a simple question: cbinary :: a - b - (a - b - b) - (b - c) - c -- Version 1 works: cbinary x y f g = g (f x y) --

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Miguel Mitrofanov
class (A x, B x, C x, D x) = U x ? 14.09.2010 12:24, Kevin Jardine пишет: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically

Re: [Haskell-cafe] Scraping boilerplate deriving?

2010-09-14 Thread Miguel Mitrofanov
Sorry, got stupid today. Won't help. 14.09.2010 12:29, Miguel Mitrofanov пишет: class (A x, B x, C x, D x) = U x ? 14.09.2010 12:24, Kevin Jardine пишет: I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C

Re: [Haskell-cafe] interesting type families problem

2010-09-08 Thread Miguel Mitrofanov
On 8 Sep 2010, at 20:01, Gábor Lehel wrote: I'm bad at expositions so I'll just lead with the code: {-# LANGUAGE EmptyDataDecls, TypeFamilies #-} data True :: * data False :: * class TypeValue a where type ValueTypeOf a :: * value :: ValueTypeOf a instance TypeValue True

Re: [Haskell-cafe] First questions!

2010-09-02 Thread Miguel Mitrofanov
02.09.2010 16:49, Eoin C. Bairéad пишет: Example 2 Prelude let fac n = if n == 0 then 1 else n * fac (n-1) How does it know to stop ? To stop what? It's not doing anything, it's just an equation. So fac is the least function which satisfies this equation - meaning that it's value would be

Re: [Haskell-cafe] Having a connection between kind * and kind * - *

2010-08-19 Thread Miguel Mitrofanov
Ivan Lazar Miljenovic wrote: I'm trying to update container-classes to duplicate the pre-existing classes defined in the Prelude (Functor, etc.) and am trying to get my approach on how to have functions/classes that work on types of kind * (e.g. Bytestring) as well as kind * - * (e.g. lists),

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

2010-08-17 Thread Miguel Mitrofanov
Ivan Lazar Miljenovic wrote: Tom Harper rtomhar...@gmail.com writes: 2010/8/17 Bulat Ziganshin bulat.zigans...@gmail.com: Hello Tom, snip i don't understand what you mean. are you support all 2^20 codepoints in Data.Text package? Bulat, Yes, its internal representation is UTF-16, which

Re: [Haskell-cafe] What is -

2010-08-08 Thread Miguel Mitrofanov
On 8 Aug 2010, at 17:36, michael rice wrote: What is - ? Couldn't find anything on Hoogle. 1) main = do x - getLine -- get the value from the IO monad putStrLn $ You typed: ++ x 2) pythags = do z - [1..] --get the value from the List monad? x - [1..z] y

Re: [Haskell-cafe] RE: Design for 2010.2.x series Haskell Platform site (Don Stewart)

2010-07-17 Thread Miguel Mitrofanov
Well, Linux fanboys are known for spending too much time with their computers compiling OS kernel or building world, no surprise their eyes aren't in place. On 18 Jul 2010, at 02:54, bri...@aracnet.com wrote: On Sat, 17 Jul 2010 18:02:05 -0400 Brandon S Allbery KF8NH allb...@ece.cmu.edu

Re: [Haskell-cafe] Subtype polymorphism in Haskell

2010-07-06 Thread Miguel Mitrofanov
of the haskell textbooks, and if anyone knows of a good in-depth treatment of this, I would be grateful for a pointer. Thanks again to everyone who responded, Simon On Mon, Jul 5, 2010 at 2:28 PM, Miguel Mitrofanov miguelim...@yandex.ru mailto:miguelim...@yandex.ru wrote: My guess is that it's

Re: [Haskell-cafe] Subtype polymorphism in Haskell

2010-07-05 Thread Miguel Mitrofanov
My guess is that it's class B : public A and class C : public A In this case it seems perfect to use type classes: class A t where do_x :: t - Integer - Integer - Integer data B = ... instance A B where do_x b x y = ... data C = ... instance A C where do_x c x y = ... If you want some general

Re: [Haskell-cafe] Re: Rewriting a famous library and using the same name: pros and cons

2010-07-03 Thread Miguel Mitrofanov
People still use Hugs? :p Is there another option for quick prototyping on iPhone? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] functional dependencies question

2010-07-01 Thread Miguel Mitrofanov
The class Num has subclasses containing various numeric types and the literal 1 is a value for one or more of those types. Well, the problem is not with subclasses, but with types. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Associated types

2010-07-01 Thread Miguel Mitrofanov
GADTs? data CompletePathEv p where CompletePathEv :: CompletePath p = CompletePathEv p class Path p = IncompletePath p where type CompletedPath p :: * completedPathEv :: CompletePathEv (CompletedPath p) Later you can pattern-match on completedPathEv and get your CompletePath

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] 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 -- above claim

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] 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 rj248...@hotmail.com: 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

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 type of (=

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] 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 [String])

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,

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 just this

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 nomin...@googlemail.com wrote: I have set a maximum width on purpose so

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

2010-04-06 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] 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

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

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

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] 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 window $

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} eqMaybe ::

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 = x == y _ == _ = False sort

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 String.

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

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' f a [] =

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

Re: [Haskell-cafe] Multi-Class monadic type?

2010-02-03 Thread Miguel Mitrofanov
Error message suggests that you've used Conf improperly. testFunc :: (forall a. Conf a, MonadIO m = m a) - TestType is illegal, as I recall, you should use another pair of brackets: testFunc :: (forall a. (Conf a, MonadIO m) = m a) - TestType Alexander Treptow wrote: Hi, i got a little

Re: [Haskell-cafe] want to post haskell question

2010-02-02 Thread Miguel Mitrofanov
|multSM d m = [[(b*a)| b-[d], a-(head m)]] Well, let's see what do we have here. We have []'s around something. Something is [(b*a)| b-[d], a-(head m)], which is just a legal Haskell value, so our mutlSM d m has to be a one-element list, with the only element being equal to what we put

Re: [Haskell-cafe] Category Theory woes

2010-02-02 Thread Miguel Mitrofanov
Hom(A, B) is just a set of morphisms from A to B. Mark Spezzano wrote: I should probably add that I am trying various proofs that involve injective and surjective properties of Hom Sets and Hom functions. Does anyone know what Hom stands for? I need a text for a newbie. Mark On 02/02/2010,

Re: [Haskell-cafe] About code style ?

2010-02-01 Thread Miguel Mitrofanov
However, i donot know how to write pure function using C style. func1 a = { -- ...; a * 2; -- ...; } What do you mean by a * 2? If you don't use this value, don't calculate it. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] UTF-16 to UTF-8

2010-01-28 Thread Miguel Mitrofanov
iconv? Günther Schmidt wrote: Hi, is there a library which converts from utf-16 to utf-8? Günther ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] classes with types which are wrapped in

2010-01-22 Thread Miguel Mitrofanov
Wrap it in a newtype. That's the only way I know. Andrew U. Frank wrote: i encounter often a problem when i have a class with some operations (say class X with push) applied to a type A b. I then wrap A in a type A_sup, with some more type parameters and i cannot write a instance of class

Re: [Haskell-cafe] Why no merge and listDiff?

2010-01-17 Thread Miguel Mitrofanov
On 17 Jan 2010, at 23:22, Will Ness wrote: What are such types called? Dependent ones. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Miguel Mitrofanov
Works fine here (Mac OS X 10.5): MigMit:ngram MigMit$ ghc --make Main.hs srilm.o [1 of 2] Compiling LM ( LM.hs, LM.o ) LM.hs:9:0: Warning: possible missing in foreign import of FunPtr [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... MigMit:ngram MigMit$ ls

Re: [Haskell-cafe] Language simplicity

2010-01-13 Thread Miguel Mitrofanov
On 13 Jan 2010, at 22:25, Andrew Coppin wrote: Colin Paul Adams wrote: Andrew It's weird that us Haskell people complain about there Andrew being only 26 letters in the alphabet Which alphabet? You have plenty of choice in Unicode. Er... I was under the impression that Haskell

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
Damn. Seems like I really need (True, False, True) as a result of test. On 7 Jan 2010, at 08:52, Miguel Mitrofanov wrote: Seems very nice. Thanks. On 7 Jan 2010, at 08:01, Edward Kmett wrote: Here is a slightly nicer version using the Codensity monad of STM. Thanks go to Andrea Vezzosi

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
PM, Miguel Mitrofanov miguelim...@yandex.ru wrote: Damn. Seems like I really need (True, False, True) as a result of test. On 7 Jan 2010, at 08:52, Miguel Mitrofanov wrote: Seems very nice. Thanks. On 7 Jan 2010, at 08:01, Edward Kmett wrote: Here is a slightly nicer version using

Re: [Haskell-cafe] Explicit garbage collection

2010-01-07 Thread Miguel Mitrofanov
. Especially as if you call it frequently you'll be dealing with a mostly cleared nursery anyways. -Edward Kmett On Thu, Jan 7, 2010 at 4:39 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote: I liked it too. Seems like I have to show some real code, and my apologies for a long e-mail. Well, that's

[Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
Is there any kind of ST monad that allows to know if some STRef is no longer needed? The problem is, I want to send some data to an external storage over a network and get it back later, but I don't want to send unnecessary data. I've managed to do something like that with weak pointers,

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
(x, y, z) so that run test returns (True, False, True). Dan Doel wrote: On Wednesday 06 January 2010 8:52:10 am Miguel Mitrofanov wrote: Is there any kind of ST monad that allows to know if some STRef is no longer needed? The problem is, I want to send some data to an external storage over

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
-Weak.html -Edward Kmett On Wed, Jan 6, 2010 at 9:39 AM, Miguel Mitrofanov miguelim...@yandex.ru wrote: I'll take a look at them. I want something like this: refMaybe b dflt ref = if b then readRef ref else return dflt refIgnore ref = return blablabla refFst ref = do (v, w) - readRef ref

Re: [Haskell-cafe] Explicit garbage collection

2010-01-06 Thread Miguel Mitrofanov
. This probably won't suit your needs, but it was a fun little exercise. -Edward Kmett On Wed, Jan 6, 2010 at 4:05 PM, Miguel Mitrofanov miguelim...@yandex.ru wrote: On 6 Jan 2010, at 23:21, Edward Kmett wrote: You probably just want to hold onto weak references for your 'isStillNeeded

Re: [Haskell-cafe] semantics of type synonym

2009-12-29 Thread Miguel Mitrofanov
pbrowne wrote: Hi, I am studying the underlying semantics behind Haskell and to what degree those semantics are actually implemented. I need to clarify what a *type synonym* actual means in relation to Haskell's logic (or formal semantics). I used the following type synonym: type Name =

Re: [Haskell-cafe] semantics of type synonym

2009-12-29 Thread Miguel Mitrofanov
1) Obviously I get two different types Wrong. You get exactly the same type, it's just that GHCi detected that you have a fancy name for this type, so it gives you that name. It's not type system, it's just GHCi. Are you saying there is just one type? (not two isomorphic types because there

Re: [Haskell-cafe] Deconstruction

2009-12-26 Thread Miguel Mitrofanov
Your code is equivalent to this: adjustToBox (ObjectWrapper object) box = adjustToBox object box but what you've probably intended to write was adjustToBox (ObjectWrapper object) box = ObjectWrapper (adjustToBox object box) It has nothing to do with existentials - it's a simple type

Re: [Haskell-cafe] Re: Allowing hyphens in identifiers

2009-12-18 Thread Miguel Mitrofanov
On 18 Dec 2009, at 06:39, Richard O'Keefe wrote: My experience has been that in order to make sense of someone else's code you *HAVE* to break identifiers into their component words. With names like (real example) ScatterColorPresetEditor, the eye *can't* take it in at once, and telling the

Re: [Haskell-cafe] Restrictions on associated types for classes

2009-12-17 Thread Miguel Mitrofanov
{-# LANGUAGE GADTs, TypeFamilies #-} module Assoc where data EqD k where EqD :: Eq k = EqD k class MyClass k where data AssociatedType k :: * evidence :: AssociatedType k - EqD (AssociatedType k) eq :: MyClass k = AssociatedType k - AssociatedType k - Bool -- eq k1 k2 = k1 == k2 --

Re: [Haskell-cafe] Restrictions on associated types for classes

2009-12-17 Thread Miguel Mitrofanov
:: MyClass k = k - AssociatedType k - AssociatedType k - Bool -- eq k k1 k2 = k1 == k2 -- doesn't work eq k k1 k2 = case evidence k of EqD - k1 == k2 -- works fine On 17 Dec 2009, at 17:10, Miguel Mitrofanov wrote: {-# LANGUAGE GADTs, TypeFamilies #-} module Assoc where data EqD k where EqD :: Eq

Re: [Haskell-cafe] Re: Allowing hyphens in identifiers

2009-12-10 Thread Miguel Mitrofanov
Not to mention that in Emacs with glasses-mode enabled camelCase can be made even more readable (my personal favorite is highlighting internal capital letters with bold). Daniel Fischer wrote: Am Mittwoch 09 Dezember 2009 23:54:22 schrieb Richard O'Keefe: Given the amazinglyUglyAndUnreadably

Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Miguel Mitrofanov
I'm constantly amused by those who manage to use Windows without installing Cygwin. On 5 Dec 2009, at 23:33, Andrew Coppin wrote: Stephen Tetley wrote: Hello Andrew Plenty compile on Windows: Some OpenVG, OpenGL[1] (still? - I'm a bit behind the times) only compile with MinGW. Others are

Re: [Haskell-cafe] Low Level Audio - Writing bytes to the sound card?

2009-12-05 Thread Miguel Mitrofanov
Try Mac. /commercial On 6 Dec 2009, at 01:00, Andrew Coppin wrote: Daniel Fischer wrote: I'm constantly amazed by those who manage to use Windows. (In case you want to misunderstand, it's not a Windows bashing, I just never managed to work with it I've not had a lot of luck with Linux.

Re: [Haskell-cafe] Is Haskell a Fanatic?

2009-12-04 Thread Miguel Mitrofanov
Well, since he thinks we're fanatics, getting a strong emotional reaction from us is something one certainly wouldn't desire. On 4 Dec 2009, at 21:14, Gregory Crosswhite wrote: Sebastian, It helps if you think of John as having already won in this discussion, since he succeeded in getting

Re: [Haskell-cafe] GHC magic optimization ?

2009-12-03 Thread Miguel Mitrofanov
Does this really mean that you want to know how the garbage collector works? Emmanuel CHANTREAU wrote: Hello One thing is magic for me: how GHC can know what function results to remember and what results can be forgotten ? Is it just a stupid buffer algorithm or is there some mathematics

  1   2   3   4   5   >