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

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

if we define this as you have:

> f1 :: Char -> Bool
> f1 'a' = True
> f1 _   = False
> 
> f2 :: Bool -> String
> f2 = show
> 
> f3 :: String -> Int
> f3 = length
> 
> fs :: F Char Int
> fs = 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                                   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume


> -----Original Message-----
> From: [EMAIL PROTECTED] 
> [mailto:[EMAIL PROTECTED] On Behalf Of Amr A Sabry
> Sent: Monday, July 28, 2003 2:22 PM
> To: [EMAIL PROTECTED]
> Cc: [EMAIL PROTECTED]
> Subject: Existentials...
> 
> 
> Hi, 
> 
> I believe this can be done with enough type hacking but I am not sure
> how...
> 
> Consider the use existentials to implement a list of composable
> functions using something like:
> 
> data F a b = 
>               forall c. PushF (a -> c) (F c b) 
>             | Bottom (a -> b)
> 
> For example:
> 
> f1 :: Char -> Bool
> f1 'a' = True
> f1 _ = False
> 
> f2 :: Bool -> String
> f2 True = "true"
> f2 False = "false"
> 
> f3 :: String -> Int
> f3 = length
> 
> fs :: F Char Int
> fs = PushF f1 (PushF f2 (PushF f3 (Bottom id)))
> 
> Is it possible to write a function 
>   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. 
> 
> I hope the question makes sense. Thanks. --Amr
> _______________________________________________
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
> 
_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to