Re: [Haskell-cafe] abstract extensible types?

2008-11-12 Thread Brandon S. Allbery KF8NH

On 2008 Nov 12, at 5:38, Alberto G. Corona wrote:
Is there any abstract container  that permits the addition of  new  
types of data? I know how to simulate the extension of Algebraic  
datatypes, but this does not permit the addition of data with new  
types in the same container and recover them in a  type-safe way.


Did I reinvent the Weel? I found something, that permits this for  
any Typeable datatype. For example



I think you want http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Dynamic.html 
 .


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] abstract extensible types?

2008-11-12 Thread Ryan Ingram
http://www.cs.nott.ac.uk/~wss/Publications/DataTypesALaCarte.pdf

This lets you create sets of types to store in a container, with the
static guarantee that only members of the set of types are included.
The types can contain other elements of the set within them
recursively.

To extract value from the container, you can provide observation
algebras that work on subsets of these values.

It's a great solution to this problem and avoids the anything with
Typeable issue that you get using Dynamic, which adds lots of
run-time failure cases if something you didn't expect makes it into
your data.

  -- ryan

2008/11/12 Alberto G. Corona [EMAIL PROTECTED]:
 Is there any abstract container  that permits the addition of  new types of
 data? I know how to simulate the extension of Algebraic datatypes, but this
 does not permit the addition of data with new types in the same container
 and recover them in a  type-safe way.

 Did I reinvent the Weel? I found something, that permits this for any
 Typeable datatype. For example


  x=5
  list= [put x,  put hello]

  [t1,t2 ]= list

  x' = get t1 :: Int
  s = get t2 :: String
  print (x' +1) -- 2
  print s-- hello

  x''= get t2 :: Int--get: casting from String  to type Int



 The code:

 data Abstract= forall a. Typeable a = T !String  a


 class FromToAbstract x where
  put :: x - Abstract
  get ::  Abstract - x
  unsafeGet :: Abstract - x

  -- get(put x)== x

 instance Typeable x = FromToAbstract x where
  put x= T (typeString x) x

  get (Abstract type1 a)= if type2 == type1 then v
 else error (get: casting ++ from type ++type1++
 to type ++type2)
where
v=  unsafeCoerce a :: x
type2= typeString v

  unsafeGet (Abstract type1 a)= unsafeCoerce a


 typeString !x= tyConString $ typeRepTyCon $ typeOf x

 instance Typeable T where
   typeOf _= mkTyConApp (mkTyCon Abstract) []

 ___
 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


[Haskell-cafe] abstract extensible types?

2008-11-12 Thread Alberto G. Corona
Is there any abstract container  that permits the addition of  new types of
data? I know how to simulate the extension of Algebraic datatypes, but this
does not permit the addition of data with new types in the same container
and recover them in a  type-safe way.

Did I reinvent the Weel? I found something, that permits this for any
Typeable datatype. For example


 x=5
 list= [put x,  put hello]

 [t1,t2 ]= list

 x' = get t1 :: Int
 s = get t2 :: String
 print (x' +1) -- 2
 print s-- hello

 x''= get t2 :: Int--get: casting from String  to type Int



The code:

data Abstract= forall a. Typeable a = T !String  a


class FromToAbstract x where
 put :: x - Abstract
 get ::  Abstract - x
 unsafeGet :: Abstract - x

 -- get(put x)== x

instance Typeable x = FromToAbstract x where
 put x= T (typeString x) x

 get (Abstract type1 a)= if type2 == type1 then v
else error (get: casting ++ from type ++type1++
to type ++type2)
   where
   v=  unsafeCoerce a :: x
   type2= typeString v

 unsafeGet (Abstract type1 a)= unsafeCoerce a


typeString !x= tyConString $ typeRepTyCon $ typeOf x

instance Typeable T where
  typeOf _= mkTyConApp (mkTyCon Abstract) []
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe