Constructing Proxy type given the input

微笑、不失礼 提交于 2019-12-13 20:00:59

问题


Given the code below which looks up type-specific information in Data.HashMap for a type, is it possible to define a new function getMapVal2 as documented in the comments, to build the TypeKey argument given the type?

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}

import Data.Monoid ((<>))
import Data.Proxy (Proxy(Proxy))
import GHC.TypeLits (KnownSymbol, Symbol, symbolVal)
import qualified Data.HashMap.Strict as Map (HashMap, empty, insert, lookup)
import Data.Dynamic
import GHC.Generics
import Data.Maybe (fromJust, isNothing, maybe)

type family TypeKey (a :: *) :: Symbol where
    TypeKey Int = "int"
    TypeKey T = "trec"

data T = T { aInt :: Int} deriving (Show, Generic, Typeable)

extract ::(s ~ TypeKey a, Typeable a, KnownSymbol s) => Maybe Dynamic -> Maybe a
extract dyn = if (isNothing dyn) then Nothing else fromDynamic . fromJust $ dyn   

getMapVal :: (s ~ TypeKey a, Typeable a, KnownSymbol s) => Map.HashMap String Dynamic -> String -> Maybe a
getMapVal m k = extract $ Map.lookup k m 

{-- How do we get the TypeKey lookup for type a?
getMapVal2 :: (s ~ TypeKey a, Typeable a, KnownSymbol s) => Map.HashMap String Dynamic -> a -> Maybe a
getMapVal2 m ty = extract $ Map.lookup (symbolVal (Proxy :: Proxy (TypeKey ???))) m
--}

main = do
  let map = Map.insert (symbolVal (Proxy :: Proxy (TypeKey T))) (toDyn $ T {aInt=5}) Map.empty -- we insert some value in hashmap for type T - it is of same type
      val = getMapVal map (symbolVal (Proxy :: Proxy (TypeKey T))) :: Maybe T -- now let us retrieve the value in map for Type T. We pass the SymbolVal ourselves
    --val =  getMapVal2 map (T {aInt = 2}) -- now we want to lookup map value given something of a type T. Need getMapVal2 to build symbolval given the input type
  print $ maybe "" show val -- prints value stored in Hashmap for type T which is: T {aInt=5}

This is just a toy code to test passing type specific configuration at run-time via Data.HashMap to a polymorphic function that acts on types of a typeclass.


回答1:


Use the ScopedTypeVariables extension. This allows you to refer to forall-bound type variables in the body of the definition in which they are bound.

{-# LANGUAGE ScopedTypeVariables #-}

getMapVal2 :: forall a s. (s ~ TypeKey a, Typeable a, KnownSymbol s) => Map.HashMap String Dynamic -> a -> Maybe a
getMapVal2 m ty = extract $ Map.lookup (symbolVal (Proxy :: Proxy (TypeKey a))) m


来源:https://stackoverflow.com/questions/36375610/constructing-proxy-type-given-the-input

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