Re: [Haskell-cafe] Alternatives to convoluted record syntax

2008-07-04 Thread Misha Aizatulin

Hi,


  busNum n
| (isBusId n) = $(modify 'query) ($(set 'queryBusNumber) (Just n))
| otherwise = id



   The solution I am using is creating for each record type @Rec@, and
each of its fields @fieldName :: T@ an updater

   updateFieldName :: (T -> T) -> Rec -> Rec

   This way you can write

busNum n
  | (isBusId n) = updateQuery $ updateQueryBusNumber $ const (Just n)
  | otherwise   = id

   The task of creating updaters can be automated using TH, this is what
the attached library does: all you need is to say

$(genUpdaters ''Opts)
$(genUpdaters ''Query)

Cheers,
   Misha



RecordUpdate.tar.gz
Description: GNU Zip compressed data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: Haddock Trac

2008-06-16 Thread Misha Aizatulin

hi,

  I wasn't able to add an attachment to a ticket, is something wrong 
with permissions?


Python Traceback

Traceback (most recent call last):
  File "/var/lib/python-support/python2.4/trac/web/main.py", line 387, 
in dispatch_request

dispatcher.dispatch(req)
  File "/var/lib/python-support/python2.4/trac/web/main.py", line 237, 
in dispatch

resp = chosen_handler.process_request(req)
  File "/var/lib/python-support/python2.4/trac/attachment.py", line 
361, in process_request

self._do_save(req, attachment)
  File "/var/lib/python-support/python2.4/trac/attachment.py", line 
494, in _do_save

attachment.insert(filename, upload.file, size)
  File "/var/lib/python-support/python2.4/trac/attachment.py", line 
180, in insert

os.makedirs(self.path)
  File "os.py", line 156, in makedirs
makedirs(head, mode)
  File "os.py", line 159, in makedirs
mkdir(name, mode)
OSError: [Errno 13] Permission denied: 
'/srv/trac/haddock/attachments/ticket'


Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Calling haddock in a portable way

2008-05-17 Thread Misha Aizatulin


>Maybe you could do something like call out to a shell and ask it to run
>'ghc --print-libdir'? That for me prints to stdout a string like
>'/usr/lib64/ghc-6.8.2'.

  Yes, this looks like a solution. Thanks a lot!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Calling haddock in a portable way

2008-05-17 Thread Misha Aizatulin

hello,

  the new version of haddock (2.0.0) needs a new option -B that tells 
it  the GHC lib directory. How do I find out the correct value for this 
option in a makefile, so that the makefile stays portable?


Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] restricted existential datatypes

2007-01-09 Thread Misha Aizatulin
hi,

  I am wondering whether it would be possible to use the existing
haskell type system to simulate a certain feature. Namely, I am trying
to apply ideas from [1] to existential datatypes. First I will describe
the problem and later say something about the context in which it arose.

  I am using existential boxes like
> data Box cxt = forall a . Sat (cxt a) => Box a
  here Sat is taken from [1]:
> class Sat a where dict :: a

  The result is a box type which can have variable context imposed on
its contents. What I noticed is that sometimes I want to write functions
that operate on the Box and make use of some part of the context without
knowing the context completely. Such a function would look something
like this:

> f :: (Contains cxt ShowCxt) => Box cxt -> String
> f (Box a) = show a

  The type is meant to say that the context of the box must contain Show
as one of the classes. I would imagine the Contains class to be
something like

> class Contains cxt subCxt where
>   subDict :: cxt a -> subCxt a

  Now inside f I would like to have the real (Show a) context available.
So I'd have an instance

> (Sat cxt a, Contains cxt ShowCxt) => Show a where
>   show = -- 

  This instance of course does not work in ghc, because cxt is
hanging in the air - I get an error whenever it tries to infer (Show a).

  The question I'd like to ask is whether there is some trickery to
circumvent this problem. In the f function I'd like to be able to hint
to the compiler that I want Show to be derived from cxt which is
attached to the Box, but I see no way of doing that. (This by the way
seems connected to
http://www.mail-archive.com/haskell@haskell.org/msg19564.html).

  Now a couple of words about where I stumbled upon this problem. I am
writing a program that is supposed to use plugins. The plugins operate
among other things on Boxes as above. Now some plugins would like to
demand some additional capabilities from the Box that cannot be foreseen
at the spot where Box is defined. Parametrizing over context seems a
very natural solution to me - leading to the problem above.

  I would be very thankful for any suggestions!

Cheers,
  Misha Aizatulin

1. John Hughes, "Restricted Data Types in Haskell", September 4, 1999


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Read Class

2006-10-28 Thread Misha Aizatulin
Tiago Veloso wrote:
> I am trying to find out how to work with the Read Class for a school
> project, i need to declare instances of Read for a few data types.
> 
> My problem is that i do not know how to do it, i mean i do not know how
> to build a Read instance, i do know about it for the Show Class.

  if you run ghc with -ddump-deriv, you will see the instances that get
generated when you use "derive".

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Guards with do notation?

2006-10-23 Thread Misha Aizatulin

hello all,

  why is it not possible to use guards in do-expressions like

  do
(a, b) | a == b <- getPair
return "a and b are equal"

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-10 Thread Misha Aizatulin
Matthias Fischmann wrote:
> Some lists have the Reply-To: set to the list address.  I think you
> can even configure the From: to be haskell-cafe instead of the poster,
> making the poster merely identifiable by the Sender: field.
> 
> Do you have strong opinions on this subject?  

  Here is an argument against Reply-To munging. I'd say I agree with it:

http://www.unicom.com/pw/reply-to-harmful.html

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] casting

2006-10-09 Thread Misha Aizatulin
Thomas Conway wrote:
> I'm having some difficulty with typeclasses.
> 
> What I'm trying to do should be obvious, but it's still giving me
> trouble. I want to take a packaged item, and strengthen the
> constraints on its type. Rather than being just any type that is an
> instance of A, I want to do a runtime check and do something different
> if it is a type that is also an instance of B (which implies that it
> is an instance of A also).

  It is not possible to check at run time, whether an instance of some
class is available for a given value. If a constraint is not mentioned
at compile time, the dictionary for that constraint will not be included
at run time, so there will be nowhere to get it from (unlike in Java,
where every object "carries" along all the dictionaries that it implements).

  Having said that there is a hack/technique that I am using myself -
maybe it will help you. It simulates something similar to what Java
does. I rewrote your program to use it - result attached here.
  The idea is to have an existential box for each class so that this box
carries the dictionary at run time. We call such a box an "interface"
and provide for our values a runtime list of interfaces that they
implement. This list is available as a function of the Interfaced class.

  You might also look at the paper "Scrap your boilerplate with class:
extensible generic functions" by Ralf Lämmel and Simon Peyton-Jones.
Among other things they describe existential boxes that can be
parametrized with the context that they carry.

Cheers,
  Misha
{-# OPTIONS_GHC -fglasgow-exts #-}

module Interface (

  Interfaced(..),
  Interface(..),
  getInterface

) where

import Data.Typeable

import Control.Monad (msum)

class Typeable a => Interfaced a where
  interfaces :: a -> [Interface]
  interfaces = const []

data Interface = forall box . Typeable box => Interface box

getInterface :: (Interfaced a, Typeable interface) => a -> Maybe interface
getInterface = msum . (map checkInterface) . interfaces where
  checkInterface (Interface interface) = cast interface
{-# OPTIONS_GHC -fglasgow-exts #-}

import Data.Typeable
import Interface

import Control.Monad

class Typeable a => A a where
baz :: a -> IO ()

data A_box = forall a . A a => A_box a deriving Typeable

class A a => B a where
qux :: a -> IO ()

data B_box = forall a . B a => B_box a deriving Typeable

{-
  returns @Just qux a@, if B constraint is implemented by a,
  otherwise @Just baz a@, if A constraint is implemented by a,
  otherwise @[EMAIL PROTECTED]
-}
tryit :: Interfaced a => a -> Maybe (IO ())
tryit a = 
  (do
B_box a' <- getInterface a
return $ qux a')
  `mplus`
  (do
A_box a' <- getInterface a
return $ baz a')

data T = T deriving Typeable

instance A T where
  baz _ = putStrLn "baz"

instance B T where
  qux _ = putStrLn "qux"

instance Interfaced T where
  interfaces a = [Interface (A_box a), Interface (B_box a)]

main = 
  case tryit T of
Just io -> io
Nothing -> putStrLn "no interface implemented"___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Haskell web forum

2006-09-21 Thread Misha Aizatulin
Kurt Hutchinson wrote:

> Let those interested in a web forum set one
> up and run it. Those interested in email can ignore the web forum.

  My concern about introducing a web forum would be that it is yet
another place I have to search every time I need information (besides
the haskell report, compiler docs and tracker, 2 wikis and the mailing
lists :)

  So setting up a web forum would only be good if it can do something a
mailing list cannot do. Following things were mentioned before:

- ease of starting new topics. Maybe. I personally end up searching
through all topics in forums anyway, because people often tend to post
in a "wrong" topic :) Christian Neumann before mentioned that mailman
might support topics as well.
  Also IMHO the current division of mailing lists (general, café,
libraries, etc.) is exactly right for organizing and separating information.

- searchability. I wouldn't agree - I can download the whole contents of
a mailing list from gmane and search it in my mail client - goes way
faster than in a forum.

- ease of access. But preventing spam would probably require
subscription just as for a mailing list.

  Any more advantages of a forum?

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sections for record settors

2006-09-19 Thread Misha Aizatulin

> It would be nice if there was some
> sort of section-like syntax to access the settor function

  Indeed - I'd like it as well. Also these threads seem to deal with
similar questions:
http://www.haskell.org/pipermail/haskell/2005-February/015354.html
http://www.haskell.org/pipermail/haskell-cafe/2005-January/008875.html
http://www.haskell.org/pipermail/template-haskell/2005-February/000409.html

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-16 Thread Misha Aizatulin
> Klaus Ostermann and I allude to this non-trivial extensibility problem 
> in our GPCE 2006 paper
> and we started to look into ways (not in that paper) to resolve
> the problem in a principled way.

  I'm really looking forward to that! For now I'll probably use Template
Haskell to register all instances that have to be serialized and output
the mapping head->type in the end.

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Deferred instance declarations (context without type variables)

2006-09-16 Thread Misha Aizatulin
hello,

  I have a question about context in type signature. I would like to
write a function, say (f :: T -> T) which also relies on an instance of
class C being defined for T. The problem is, I don't want this instance
defined at the same time f is defined, instead I would like to defer
this definition until f is called (in some other module). Naively the
code would look like this:
=
module DefineF where

class C a where
  fC :: a -> a

data T = T

f :: (C T) => T -> T
f T = fC T
=
module CallF where

instance C T where
  fC = id

call = f T
=
  The definition of f in DefineF won't compile because "All of the type
variables .. are already in scope". Could you recommend any other way to
achieve what I am trying to do?

  An interesting thing is that I can easily make the code compile with
the same meaning by changing the 
declaration of T to include a dummy type variable:
> data T a = T
  it's just a pity that I have to trick the compiler in such an ugly
way.

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-13 Thread Misha Aizatulin
Einar Karttunen wrote:
> >   I've been using existentially quantified data constructors like
> > 
> > > data Box = forall a. Cxt a => Box a
> 
> If you can include Typeable into the mix then serializing works.
> 
> Serialize the value as " ".
> 
> When deserializing use a Map  
> and get the appropriate decoder from there for the type in question.

  This is indeed the only solution I see so far. It has a serious
problem though: as soon as I write the mapping, I limit once and for all
the set of all types that can be used with my box. And I do so in a
non-extensible way - if someone later would like to use my box with some
other type in it, they wouldn't be able to.

  In fact, I start wondering, how OO languages solve the same problem.
I'll take a look at Java now.

Cheers,
   Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Serialising types with existential data constructors

2006-09-12 Thread Misha Aizatulin
Bulat Ziganshin wrote:

>> data Box = forall a. Cxt a => Box a
>>   quite successfully for a while. But now I am trying to implement the
>> Load/Save mechanism and getting stuck with that. It's not hard to write
>> a Box into a file, but how do I get it back?
> 
> gshow/gread provided by module Data.Generics.Text

  I am afraid this won't do it. For gread to work I still need to know
the result type before I call it, but the problem with the Box is
exactly that you don't know the type it will contain in advance.

  Maybe there is a way to dump the binary representation of the whole
box and then read it back (using unsafeCoerce or similar stuff on the way)?

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Serialising types with existential data constructors

2006-09-12 Thread Misha Aizatulin
hello all,

  I've been using existentially quantified data constructors like

> data Box = forall a. Cxt a => Box a

  quite successfully for a while. But now I am trying to implement the
Load/Save mechanism and getting stuck with that. It's not hard to write
a Box into a file, but how do I get it back?

  Has anyone solved the same problem before? I would be very thankful
for any suggestions!

  If Template Haskell would support finding out all instances of a given
class, I could generate a function that would map Names of types to
appropriate Box readers. In the file I would write entries like
 : 

  But sadly, TH doesn't allow that yet.

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-09-09 Thread Misha Aizatulin
Daniel Fischer wrote:

> Another thing:
> Would it be a good idea to create derived Read instances that could parse 
> both, "A `And` A" and "And A A" ?
> Since 6.4.2 parses the former and 6.2.2 parses the latter that should be 
> possible, I believe (and both forms are accepted at the ghci prompt).

  I made a Template Haskell function that does exactly that. I wrote
about it to the template-haskell list:

http://www.haskell.org/pipermail/template-haskell/2006-September/000587.html

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-08-26 Thread Misha Aizatulin
Ian Lynagh wrote:

> ghci on 6.4.2 Linux works for me:

  oops, works for me too - I forgot the type annotation when calling
read :) So it's fine in 6.4.2 - sorry for the disturbance then!

Cheers,
  Misha

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-08-26 Thread Misha Aizatulin
Jason Dagit wrote:

> Before you get too caught up in deriving Read, remember that in
> Haskell it's very easy to create your own custom parser.  Assuming you
> have previous experience with happy or parsec you could probably have
> already created a custom parser with time you've spent debugging this
> automatic Read instance flaw.  And if you had your own parser couldn't
> you define read to use that parser?  Just a thought...

  You are right, I will probably end up rolling my own instances with
Template Haskell or DrIFT (there are a lot of types where I need these
instances). I just wanted to make sure that I'm not missing something
stupid and that there is no easier way to do that.

  By the way, if someone already has TH code for deriving Read
instances, sharing would be greatly appreciated :)

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-08-26 Thread Misha Aizatulin
Neil Mitchell wrote:
>> *Main> show $ A `And` A
>> "A And A"
> 
> For me, using GHCi 6.4.2 + Windows, I get:
> "A `And` A"

  I installed GHC 6.4.2 now (on Linux). It really does print "A `And`
A", but still doesn't read it. Would you agree that GHC doesn't conform
to the Haskell Report here? In fact it seems to produce a Read instance
with no valid input for it!

Daniel Fischer wrote:
> Put the constructor in the prefix position in the data definition and
> the derived Read instance of ghc 6.4.1 will also be able to read the
> prefix form.

  This might be a solution, but I was hoping that I can have a Read
instance that would read the infix form - this would be more natural for
the data I have (like logical expressions).

Cheers,
  Misha
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-08-25 Thread Misha Aizatulin
hi,

  the Haskell Report 10.4 says that

"The result of show is readable by read if all component types are readable"

  however if I define a type like

data T = A | T `And` T deriving (Read, Show)

  then

*Main> show $ A `And` A
"A And A"
*Main> (read "A And A") :: T
*** Exception: Prelude.read: no parse
*Main>

  In fact, I wasn't able to guess, what I should type so that the value
(A `And` A) gets parsed.

  I have ghc 6.4.1. Looking into the code of the derived instance I see
that it expects Text.Read.Lex.lex to return (Symbol "And") for the
constructor. If I understand the code for lex correctly, then it parses
things as Symbol if they consist only of
"[EMAIL PROTECTED]&*+./<=>?\\^|:-~"

  How then do I read values of type T defined above? Thanks in advance
for any directions.

Cheers,
  Misha

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe