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

2010-07-28 Thread Serguey Zefirov
2010/7/28 Simon Peyton-Jones :
> I assume you've seen http://hackage.haskell.org/trac/ghc/ticket/4222
> There are non-obvious design choices here

Yes, I've seen that. Right now I just cannot grok it fully. I feel
like I should share my current understanding with cafe, so I wrote
them in my answer to Jonas.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-28 Thread Simon Peyton-Jones
I assume you've seen http://hackage.haskell.org/trac/ghc/ticket/4222
There are non-obvious design choices here

Simon

| -Original Message-
| From: haskell-cafe-boun...@haskell.org 
[mailto:haskell-cafe-boun...@haskell.org] On
| Behalf Of Serguey Zefirov
| Sent: 28 July 2010 11:07
| To: Jonas Almström Duregård
| Cc: Ivan Lazar Miljenovic; haskell
| Subject: Re: [Haskell-cafe] Template Haskell sees into abstract data types
| 
| 2010/7/28 Jonas Almström Duregård :
| > Hi,
| >
| >> I cannot write classes that see into internal structure. For example,
| >> I cannot write my own (de)serialization without using from/toAscList.
| >
| > Actually I don't believe you can do this with TH either. TH splices
| > code into the module where you use it. The generated code is then type
| > checked in this module. If constructors that are not exported are used
| > in the generated code, I believe you will get an error.
| >
| > This could still be an issue because your TH code won't know if the
| > constructors are exported or not, but i doubt you can actually do
| > things with TH that you can't do with plain H.
| 
| I doubt that doubt first. ;)
| 
| >> At least, it looks like I can, I didn't tried, actually.
| > Neither have I.
| 
| So I did. And succeed: TH sees into data types.
| 
| (ghc 6.12.1)
| 
| Module A.hs, contains definition of abstract data type A, class Class
| and some primitive instance generator for that Class. Instance
| generator takes a data declaration name, takes first constructor
| (which should be argumentless) and makes it a value for definition of
| "c" function.
| --
| {-# LANGUAGE TemplateHaskell #-}
| 
| module A(A,Class(..),mkSimpleClass) where
| 
| import Language.Haskell.TH
| 
| data A = A1 | A2
|   deriving Show
| 
| class Class a where
|   c :: a
| 
| mkSimpleClass :: Name -> Q [Dec]
| mkSimpleClass name = do
|   TyConI (DataD [] dname [] cs _) <- reify name
|   ((NormalC conname []):_) <- return cs
|   ClassI (ClassD [] cname [_] [] [SigD mname _]) <- reify ''Class
|   return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
| [Clause [] (NormalB (ConE conname)) [
| --
| 
| Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
| --
| {-# LANGUAGE TemplateHaskell #-}
| 
| module B where
| 
| import A
| 
| $(mkSimpleClass ''A)
| --
| 
| I successfully loaded B.hs into ghci, Expression "c :: A" successfully
| evaluates to A1.
| 
| My view on that problem is that we can add TyConIAbs for incompletely
| exported and abstract data types.
| 
| When someone get TyConIAbs after reification, he will know that he
| doesn't know everything about that type.
| 
| So, empty data declaration like "data Z" will return TyConI with empty
| list of constructors, TyConIAbs will have empty list of constructors
| for abstract data type.
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe

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


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

2010-07-28 Thread Gábor Lehel
On Wed, Jul 28, 2010 at 12:55 PM, Gábor Lehel  wrote:
> 2010/7/28 Serguey Zefirov :
>> 2010/7/28 Jonas Almström Duregård :
>>> Hi,
>>>
 I cannot write classes that see into internal structure. For example,
 I cannot write my own (de)serialization without using from/toAscList.
>>>
>>> Actually I don't believe you can do this with TH either. TH splices
>>> code into the module where you use it. The generated code is then type
>>> checked in this module. If constructors that are not exported are used
>>> in the generated code, I believe you will get an error.
>>>
>>> This could still be an issue because your TH code won't know if the
>>> constructors are exported or not, but i doubt you can actually do
>>> things with TH that you can't do with plain H.
>>
>> I doubt that doubt first. ;)
>>
 At least, it looks like I can, I didn't tried, actually.
>>> Neither have I.
>>
>> So I did. And succeed: TH sees into data types.
>>
>> (ghc 6.12.1)
>>
>> Module A.hs, contains definition of abstract data type A, class Class
>> and some primitive instance generator for that Class. Instance
>> generator takes a data declaration name, takes first constructor
>> (which should be argumentless) and makes it a value for definition of
>> "c" function.
>> --
>> {-# LANGUAGE TemplateHaskell #-}
>>
>> module A(A,Class(..),mkSimpleClass) where
>>
>> import Language.Haskell.TH
>>
>> data A = A1 | A2
>>        deriving Show
>>
>> class Class a where
>>        c :: a
>>
>> mkSimpleClass :: Name -> Q [Dec]
>> mkSimpleClass name = do
>>        TyConI (DataD [] dname [] cs _) <- reify name
>>        ((NormalC conname []):_) <- return cs
>>        ClassI (ClassD [] cname [_] [] [SigD mname _]) <- reify ''Class
>>        return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
>> [Clause [] (NormalB (ConE conname)) [
>> --
>>
>> Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
>> --
>> {-# LANGUAGE TemplateHaskell #-}
>>
>> module B where
>>
>> import A
>>
>> $(mkSimpleClass ''A)
>> --
>>
>> I successfully loaded B.hs into ghci, Expression "c :: A" successfully
>> evaluates to A1.
>>
>> My view on that problem is that we can add TyConIAbs for incompletely
>> exported and abstract data types.
>>
>> When someone get TyConIAbs after reification, he will know that he
>> doesn't know everything about that type.
>>
>> So, empty data declaration like "data Z" will return TyConI with empty
>> list of constructors, TyConIAbs will have empty list of constructors
>> for abstract data type.
>
> You can also export just *some* constructors, though. This would
> distinguish between  "module Foo (A(..)) where data A" and "module Foo
> (A) where data A = A", but what about "module Bar (B(..)) where data B
> = B" and "module Bar (B(B)) where data B = B | C | D"?

Never mind -- I see you mentioned "incompletely exported" already.

You could also just add a Bool parameter to TyConI signifying whether
some constructors are hidden. (Also, I imagine this doesn't just apply
to data types, but also say type classes.)


>
>
>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>
>
>
> --
> Work is punishment for failing to procrastinate effectively.
>



-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-28 Thread Gábor Lehel
2010/7/28 Serguey Zefirov :
> 2010/7/28 Jonas Almström Duregård :
>> Hi,
>>
>>> I cannot write classes that see into internal structure. For example,
>>> I cannot write my own (de)serialization without using from/toAscList.
>>
>> Actually I don't believe you can do this with TH either. TH splices
>> code into the module where you use it. The generated code is then type
>> checked in this module. If constructors that are not exported are used
>> in the generated code, I believe you will get an error.
>>
>> This could still be an issue because your TH code won't know if the
>> constructors are exported or not, but i doubt you can actually do
>> things with TH that you can't do with plain H.
>
> I doubt that doubt first. ;)
>
>>> At least, it looks like I can, I didn't tried, actually.
>> Neither have I.
>
> So I did. And succeed: TH sees into data types.
>
> (ghc 6.12.1)
>
> Module A.hs, contains definition of abstract data type A, class Class
> and some primitive instance generator for that Class. Instance
> generator takes a data declaration name, takes first constructor
> (which should be argumentless) and makes it a value for definition of
> "c" function.
> --
> {-# LANGUAGE TemplateHaskell #-}
>
> module A(A,Class(..),mkSimpleClass) where
>
> import Language.Haskell.TH
>
> data A = A1 | A2
>        deriving Show
>
> class Class a where
>        c :: a
>
> mkSimpleClass :: Name -> Q [Dec]
> mkSimpleClass name = do
>        TyConI (DataD [] dname [] cs _) <- reify name
>        ((NormalC conname []):_) <- return cs
>        ClassI (ClassD [] cname [_] [] [SigD mname _]) <- reify ''Class
>        return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
> [Clause [] (NormalB (ConE conname)) [
> --
>
> Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
> --
> {-# LANGUAGE TemplateHaskell #-}
>
> module B where
>
> import A
>
> $(mkSimpleClass ''A)
> --
>
> I successfully loaded B.hs into ghci, Expression "c :: A" successfully
> evaluates to A1.
>
> My view on that problem is that we can add TyConIAbs for incompletely
> exported and abstract data types.
>
> When someone get TyConIAbs after reification, he will know that he
> doesn't know everything about that type.
>
> So, empty data declaration like "data Z" will return TyConI with empty
> list of constructors, TyConIAbs will have empty list of constructors
> for abstract data type.

You can also export just *some* constructors, though. This would
distinguish between  "module Foo (A(..)) where data A" and "module Foo
(A) where data A = A", but what about "module Bar (B(..)) where data B
= B" and "module Bar (B(B)) where data B = B | C | D"?



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



-- 
Work is punishment for failing to procrastinate effectively.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-28 Thread Serguey Zefirov
2010/7/28 Jonas Almström Duregård :
> Hi,
>
>> I cannot write classes that see into internal structure. For example,
>> I cannot write my own (de)serialization without using from/toAscList.
>
> Actually I don't believe you can do this with TH either. TH splices
> code into the module where you use it. The generated code is then type
> checked in this module. If constructors that are not exported are used
> in the generated code, I believe you will get an error.
>
> This could still be an issue because your TH code won't know if the
> constructors are exported or not, but i doubt you can actually do
> things with TH that you can't do with plain H.

I doubt that doubt first. ;)

>> At least, it looks like I can, I didn't tried, actually.
> Neither have I.

So I did. And succeed: TH sees into data types.

(ghc 6.12.1)

Module A.hs, contains definition of abstract data type A, class Class
and some primitive instance generator for that Class. Instance
generator takes a data declaration name, takes first constructor
(which should be argumentless) and makes it a value for definition of
"c" function.
--
{-# LANGUAGE TemplateHaskell #-}

module A(A,Class(..),mkSimpleClass) where

import Language.Haskell.TH

data A = A1 | A2
deriving Show

class Class a where
c :: a

mkSimpleClass :: Name -> Q [Dec]
mkSimpleClass name = do
TyConI (DataD [] dname [] cs _) <- reify name
((NormalC conname []):_) <- return cs
ClassI (ClassD [] cname [_] [] [SigD mname _]) <- reify ''Class
return [InstanceD [] (AppT (ConT cname) (ConT dname)) [FunD mname
[Clause [] (NormalB (ConE conname)) [
--

Module B.hs, imports A.hs, uses mkSimpleClass on A.A name:
--
{-# LANGUAGE TemplateHaskell #-}

module B where

import A

$(mkSimpleClass ''A)
--

I successfully loaded B.hs into ghci, Expression "c :: A" successfully
evaluates to A1.

My view on that problem is that we can add TyConIAbs for incompletely
exported and abstract data types.

When someone get TyConIAbs after reification, he will know that he
doesn't know everything about that type.

So, empty data declaration like "data Z" will return TyConI with empty
list of constructors, TyConIAbs will have empty list of constructors
for abstract data type.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-28 Thread Jonas Almström Duregård
Hi,

> I cannot write classes that see into internal structure. For example,
> I cannot write my own (de)serialization without using from/toAscList.

Actually I don't believe you can do this with TH either. TH splices
code into the module where you use it. The generated code is then type
checked in this module. If constructors that are not exported are used
in the generated code, I believe you will get an error.

This could still be an issue because your TH code won't know if the
constructors are exported or not, but i doubt you can actually do
things with TH that you can't do with plain H.

> At least, it looks like I can, I didn't tried, actually.

Neither have I.

/J

On 4 July 2010 01:10, Serguey Zefirov  wrote:
>>> I cannot directly create my own class instances for them because of
>>> that. But I found that I can write Template Haskell code that could do
>>> that - those data types could be reified just fine.
>> Huh?  Sure you can write class instances for them.
>> ,
>> | instance SizeOf (Map k v) where
>> |   sizeOf = Map.size
>> `
>
> Those are trivial. They are not interesting.
>
> I cannot write classes that see into internal structure. For example,
> I cannot write my own (de)serialization without using from/toAscList.
>
>>> This is somewhat strange situation.
>>> Was it a design decision?
>> The reason that they are exported abstractly is so that you don't see
>> the internals of the data structure, because 1) you don't need to, and
>> 2) to stop you from doing anything stupid with them.
>
> I was talking about successful reification of abstract data types.
>
> That way I can do anything stupid with them.
>
> At least, it looks like I can, I didn't tried, actually.
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-26 Thread Simon Peyton-Jones
|  Data.Map.Map and Data.Set.Set are exported abstractly, without
|  exposing knowledge about their internal structure.
|  
|  I cannot directly create my own class instances for them because of
|  that. But I found that I can write Template Haskell code that could do
|  that - those data types could be reified just fine.

I've created a ticket for this http://hackage.haskell.org/trac/ghc/ticket/4222. 
 

In writing it down I identify several design questions that need to be 
addressed before we can "fix" this bug.  Help welcome.

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


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

2010-07-03 Thread Brandon S Allbery KF8NH
-BEGIN PGP SIGNED MESSAGE-
Hash: SHA1

On 7/4/10 00:29 , Ivan Lazar Miljenovic wrote:
> David Menendez  writes:
>> I believe the point is that Template Haskell can see the internal
>> structure of a type even when the constructors are not exported. The
>> question is whether or not that is intentional.
> 
> I was under the impression that the question was whether the hiding of
> the constructors, etc. was intentional...

No, he knew that ("abstract types" from the original message).  The question
was whether TH is supposed to be able to violate the abstraction barrier.

- -- 
brandon s. allbery [linux,solaris,freebsd,perl]  allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university  KF8NH
-BEGIN PGP SIGNATURE-
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkwwEdIACgkQIn7hlCsL25W+9gCgmUI5P5wdCDXoHjqJkx5lH5U2
ZFsAnjAeCfVAsFjHBpozp1D5BFG3kCKW
=c51E
-END PGP SIGNATURE-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-03 Thread Ivan Lazar Miljenovic
David Menendez  writes:

> I believe the point is that Template Haskell can see the internal
> structure of a type even when the constructors are not exported. The
> question is whether or not that is intentional.

I was under the impression that the question was whether the hiding of
the constructors, etc. was intentional...

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

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

 This is somewhat strange situation.  Was it a design decision?
>>> The reason that they are exported abstractly is so that you don't see
>>> the internals of the data structure, because 1) you don't need to, and
>>> 2) to stop you from doing anything stupid with them.
>>
>> I was talking about successful reification of abstract data types.
>>
>> That way I can do anything stupid with them.
>
> Why do you want to?

I believe the point is that Template Haskell can see the internal
structure of a type even when the constructors are not exported. The
question is whether or not that is intentional.

-- 
Dave Menendez 

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


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

2010-07-03 Thread Ivan Lazar Miljenovic
Serguey Zefirov  writes:

>>> I cannot directly create my own class instances for them because of
>>> that. But I found that I can write Template Haskell code that could do
>>> that - those data types could be reified just fine.
>> Huh?  Sure you can write class instances for them.
>> ,
>> | instance SizeOf (Map k v) where
>> |   sizeOf = Map.size
>> `
>
> Those are trivial. They are not interesting.

You said you couldn't write any, and of course I wrote a trivial one
because I didn't want to write a whole library in an email.

> I cannot write classes that see into internal structure. For example,
> I cannot write my own (de)serialization without using from/toAscList.

So?  What's wrong with using {from,to}AscList ?

You could also try using GHC's stand-alone deriving mechanism to derive
binary or something:

http://www.haskell.org/haskellwiki/GHC/Stand-alone_deriving_declarations

>>> This is somewhat strange situation.  Was it a design decision?
>> The reason that they are exported abstractly is so that you don't see
>> the internals of the data structure, because 1) you don't need to, and
>> 2) to stop you from doing anything stupid with them.
>
> I was talking about successful reification of abstract data types.
>
> That way I can do anything stupid with them.

Why do you want to?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-03 Thread Serguey Zefirov
>> I cannot directly create my own class instances for them because of
>> that. But I found that I can write Template Haskell code that could do
>> that - those data types could be reified just fine.
> Huh?  Sure you can write class instances for them.
> ,
> | instance SizeOf (Map k v) where
> |   sizeOf = Map.size
> `

Those are trivial. They are not interesting.

I cannot write classes that see into internal structure. For example,
I cannot write my own (de)serialization without using from/toAscList.

>> This is somewhat strange situation.
>> Was it a design decision?
> The reason that they are exported abstractly is so that you don't see
> the internals of the data structure, because 1) you don't need to, and
> 2) to stop you from doing anything stupid with them.

I was talking about successful reification of abstract data types.

That way I can do anything stupid with them.

At least, it looks like I can, I didn't tried, actually.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-07-03 Thread Ivan Lazar Miljenovic
Serguey Zefirov  writes:

> Data.Map.Map and Data.Set.Set are exported abstractly, without
> exposing knowledge about their internal structure.
>
> I cannot directly create my own class instances for them because of
> that. But I found that I can write Template Haskell code that could do
> that - those data types could be reified just fine.

Huh?  Sure you can write class instances for them.

,
| 
| import qualified Data.Map as Map
| import Data.Map(Map)
| import qualified Data.Set as Set
| import Data.Set(Set)
| 
| class SizeOf x where
|   sizeOf :: x -> Int
| 
| instance SizeOf [a] where
|   sizeOf = length
| 
| instance SizeOf (Set a) where
|   sizeOf = Set.size
| 
| instance SizeOf (Map k v) where
|   sizeOf = Map.size
`

> This is somewhat strange situation.
>
> Was it a design decision?

The reason that they are exported abstractly is so that you don't see
the internals of the data structure, because 1) you don't need to, and
2) to stop you from doing anything stupid with them.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe