Existentials...

Hal Daume t-hald@microsoft.com
Mon, 28 Jul 2003 16:21:58 -0700


Sure it's possible :)...using the GMap library...heres an
implementation:

> module PushF where
>=20
> import GMap.Adhoc
> import GMap.GenericLib
> import GMap.Term
> import Data.Dynamic
>=20
> data F a b =3D forall c. (Typeable c, Term c) =3D> PushF (a -> c) (F c =
b)
>            | Bottom (a -> b)
>=20
> _tc_F =3D mkTyCon "F"
> instance (Typeable a, Typeable b) =3D> Typeable (F a b) where
>     typeOf (_ :: F a b) =3D mkAppTy _tc_F [typeOf (undefined::a), =
typeOf
(undefined::b)]
>=20
> instance (Term a, Term b) =3D> Term (F a b) where
>   gmapT  f   (Bottom  x) =3D Bottom x
>   gmapT  f   (PushF g h) =3D PushF g (f h)
>   gfoldl f z (Bottom  x) =3D z (Bottom x)
>   gfoldl f z (PushF g h) =3D z (PushF g) `f` h
>=20
> getInner :: (Typeable a, Typeable b, Typeable c, Term (F a b)) =3D> F =
a
b -> c -> Maybe (F c b)
> getInner (x :: F a b) (c :: c) =3D something (isCToB (undefined::c)
(undefined::b)) x
>=20
> isCToB :: (Typeable t, Typeable c, Typeable b) =3D> c -> b -> t -> =
Maybe
(F c b)
> isCToB (c::c) (b::b) t =3D cast t

if we define this as you have:

> f1 :: Char -> Bool
> f1 'a' =3D True
> f1 _   =3D False
>=20
> f2 :: Bool -> String
> f2 =3D show
>=20
> f3 :: String -> Int
> f3 =3D length
>=20
> fs :: F Char Int
> fs =3D f1 `PushF` (f2 `PushF` (f3 `PushF` (Bottom id)))

then we can do the following:

*PushF> Maybe.isJust (getInner fs 'a')
True
*PushF> Maybe.isJust (getInner fs "hello")
True
*PushF> Maybe.isJust (getInner fs True)
True
*PushF> Maybe.isJust (getInner fs (1::Int))
True
*PushF> Maybe.isJust (getInner fs (1::Float))
False
*PushF> Maybe.isJust (getInner fs ())
False


hope this helps.

 - hal

--
 Hal Daume III                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: haskell-admin@haskell.org=20
> [mailto:haskell-admin@haskell.org] On Behalf Of Amr A Sabry
> Sent: Monday, July 28, 2003 2:22 PM
> To: haskell@haskell.org
> Cc: sabry@cs.indiana.edu
> Subject: Existentials...
>=20
>=20
> Hi,=20
>=20
> I believe this can be done with enough type hacking but I am not sure
> how...
>=20
> Consider the use existentials to implement a list of composable
> functions using something like:
>=20
> data F a b =3D=20
>               forall c. PushF (a -> c) (F c b)=20
>             | Bottom (a -> b)
>=20
> For example:
>=20
> f1 :: Char -> Bool
> f1 'a' =3D True
> f1 _ =3D False
>=20
> f2 :: Bool -> String
> f2 True =3D "true"
> f2 False =3D "false"
>=20
> f3 :: String -> Int
> f3 =3D length
>=20
> fs :: F Char Int
> fs =3D PushF f1 (PushF f2 (PushF f3 (Bottom id)))
>=20
> Is it possible to write a function=20
>   f :: F a b -> T c -> F c b
> where (T c) is some type for values of type 'c' or values representing
> the type 'c' or whatever is appropriate. Thus if given the
> representation of Bool, the function should return:
>  PushF f2 (PushF f3 (Bottom id))
> and if given the representation of String the function should return
>  PushF f3 (Bottom id)
> and so on.=20
>=20
> I hope the question makes sense. Thanks. --Amr
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>=20