Using Typeable to partially apply function at run-time (any time types match)

泄露秘密 提交于 2019-12-22 05:43:19

问题


Generic programming time!

If I have a function:

f :: a1 -> a2 -> a3 -> ... -> an

and a value

v :: aX   -- where 1 <= x < n

Without knowing at compile time which of the arguments of f the value v is the right type for (if any), can I partially apply f to v? (using Typeable, Data, TH, or any other trick)

Slightly more solidly, can I construct the function g (below) at run-time? It doesn't actually have to be polymorphic, all my types will be monomorphic!

g :: (a1 -> a2 -> a3 -> a4 -> a5) -> a3 -> (a1 -> a2 -> a4 -> a5)
g f v = \x y z -> f x y v z

I know that, using Typeable (typeRepArgs specifically), v is the 3rd argument of f, but that doesn't mean I have a way to partially apply f.

My code would probably look like:

import Data.Typeable

data Box = forall a. Box (TyRep, a)

mkBox :: Typeable a => a -> Box
mkBox = (typeOf a, a)

g :: Box -> Box -> [Box]
g (Box (ft,f)) (Box (vt,v)) = 
    let argNums = [n | n <- [1..nrArgs], isNthArg n vt ft]
    in map (mkBox . magicApplyFunction f v) argNums

isNthArg :: Int -> TyRep -> TyRep -> Bool
isNthArg n arg func = Just arg == lookup n (zip [1..] (typeRepArgs func))

nrArgs :: TyRep -> Int
nrArgs = (\x -> x - 1) . length . typeRepArgs

Is there anything that can implement the magicApplyFunction?

EDIT: I finally got back to playing with this. The magic apply function is:

buildFunc :: f -> x -> Int -> g
buildFunc f x 0 = unsafeCoerce f x
buildFunc f x i =
        let !res = \y -> (buildFunc (unsafeCoerce f y) x (i-1))
        in unsafeCoerce res

回答1:


I'm not going to write the whole solution here for now, but I'm sure this can be done purely with Data.Dynamic and Typeable. The source for dynApply and funResultTy should provide the key elements:

dynApply :: Dynamic -> Dynamic -> Maybe Dynamic
dynApply (Dynamic t1 f) (Dynamic t2 x) =
  case funResultTy t1 t2 of
    Just t3 -> Just (Dynamic t3 ((unsafeCoerce f) x))
    Nothing -> Nothing


funResultTy :: TypeRep -> TypeRep -> Maybe TypeRep
funResultTy trFun trArg
  = case splitTyConApp trFun of
      (tc, [t1,t2]) | tc == funTc && t1 == trArg -> Just t2
      _ -> Nothing

To keep things simple, I'd have type Box = (Dynamic, [Either TypeRep Dynamic]). The latter starts out as a list of typereps of arguments. magicApply would look for the first matching TypeRep in the box and substitute the Dynamic of the value. Then you could have an extract that given a Box to which all arguments have been magicapplied, actually performs the dynApply calls to produce the resulting dynamic result.




回答2:


Hm.. Typeable only? How about good old OverlappingInstances?

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, TypeFamilies,
UndecidableInstances, IncoherentInstances, ScopedTypeVariables #-}

class Magical a b c where
    apply :: a -> b -> c

instance (AreEqual a c e, Magical' e (a -> b) c r) => Magical (a -> b) c r where
    apply f a = apply' (undefined :: e) f a


class Magical' e a b c where
    apply' :: e -> a -> b -> c

instance (r ~ b) => Magical' True (a -> b) a r where
    apply' _ f a = f a

instance (Magical b c d, r ~ (a -> d)) => Magical' False (a -> b) c r where
    apply' _ f c = \a -> apply (f a) c


data True
data False

class AreEqual a b r
instance (r ~ True) => AreEqual a a r
instance (r ~ False) => AreEqual a b r


test :: Int -> Char -> Bool
test i c = True

t1 = apply test (5::Int)
t2 = apply test 'c'


来源:https://stackoverflow.com/questions/5745302/using-typeable-to-partially-apply-function-at-run-time-any-time-types-match

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!