forall quantifier
Tomasz Zielonka
t.zielonka@students.mimuw.edu.pl
Wed, 4 Jun 2003 17:45:31 +0200
On Wed, Jun 04, 2003 at 04:43:10PM +0200, Markus.Schnell@infineon.com wrote:
> Yes, this would work, thanks.
>
> But let me extent my question: what if all the types would be in a
> class FakeClass which has function specialID :: a -> ID and
> I would like to do
>
> > foo $ map specialID [a,b,c,d]
> ?
Well, in Template Haskell you can do:
{-# OPTIONS -fglasgow-exts #-}
module B where
import Language.Haskell.THSyntax
data AnyShow = forall s. Show s => AnyShow s
instance Show AnyShow where
show (AnyShow s) = show s
metaMap :: ExpQ -> ExpQ -> ExpQ
metaMap qf ql = do
l <- ql
case l of
Infix (Just x) (Con "GHC.Base::") (Just xs) -> do
let ys = metaMap qf (return xs)
[| ($qf $(return x) : $ys) |]
Con "GHC.Base:[]" -> do
[| [] |]
ListExp xs -> do
ys <- sequence [ [| $qf $(return x) |] | x <- xs ]
return $ ListExp ys
other -> do
fail $ "metaMap: unexpected syntax: " ++ show other
and then:
map show $( metaMap [| AnyShow |] [| [1, 1.3, [1,2,3,4]] |]
and
map show $( metaMap [| AnyShow |] [| [1, 1.3, 'a'] |]
will work, but this won't
map show $( metaMap [| AnyShow |] [| [1, 1.3, 'a', [1,2,3,4]] |]
Is there a way to turn of typing within meta quotations?
Best regards,
Tom
--
.signature: Too many levels of symbolic links