errfrom
errfrom

Reputation: 253

How to specify type of value via 'TypeRep'?

My aim is to write function that takes some polymorphic values and list with typereps representing concrete types. It returns new list with the same values but already casted to concrete types specified via typereps.

Let we have such list of values: ["one", "two"] with -XOverloadedStrings enabled.
Respectively, type of each one is IsString a => a.

List of typereps we could get in such way:

import Data.Typeable (Proxy(..), typeRep)
import Data.Text     (Text)

[typeRep (Proxy :: Proxy String), typeRep (Proxy :: Proxy ByteString)]

Is there any way to get "one" of type String and "two" of type ByteString?

P.S. To prevent error according to list containing values of different types, we may wrap every value in Dynamic., as in the example below(pseudocode):

 {-# LANGUAGE ParallelListComp #-}

 import Data.Dynamic (toDyn)

 [ toDyn (val :: type') | val <- vals | type' <- concreteTypes ]

It could be done using Template Haskell, but it will be too ugly.

Upvotes: 1

Views: 364

Answers (2)

dfeuer
dfeuer

Reputation: 48611

I can't really imagine your purpose, but the code will probably look something like this. I'm using the new Type.Reflection interface because I'm more familiar with it than with the classic Data.Typeable, but that should work for this too.

import Type.Reflection

types :: [SomeTypeRep]
types = [SomeTypeRep (typeRep @String), SomeTypeRep (typeRep @Text)]

strings :: [String]
strings = ["one", "two"]

converted :: [Dynamic]
converted = fromJust $ zipWithM convert types strings

convert :: SomeTypeRep -> String -> Maybe Dynamic
convert (SomeTypeRep rep) s
  | Just HRefl <- eqTypeRep rep (typeRep @String) = Just $ toDynamic s
  | Just HRefl <- eqTypeRep rep (typeRep @Text) = Just $ toDynamic (fromString s)
  | otherwise = Nothing

Upvotes: 6

Daniel Wagner
Daniel Wagner

Reputation: 153172

Hold my beer.

{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE OverloadedStrings #-}

import Data.ByteString (ByteString)
import Data.String
import Data.Text (Text)

data Forall c where Forall :: (forall a. c a => a) -> Forall c
data Exists c where Exists :: c a => a -> Exists c
data Evidence c where Evidence :: c a => proxy a -> Evidence c

instance c ~ IsString => IsString (Forall c) where
    fromString s = Forall (fromString s)

asProxyType :: proxy a -> a -> a
asProxyType = const id

downcast :: Evidence c -> Forall c -> Exists c
downcast (Evidence proxy) (Forall v) = Exists (asProxyType proxy v)

polymorphicStrings :: c ~ IsString => [Forall c]
polymorphicStrings = ["one", "two"]

types :: c ~ IsString => [Evidence c]
types = [Evidence ([] :: [ByteString]), Evidence ([] :: [Text])]

monomorphicStrings :: c ~ IsString => [Exists c]
monomorphicStrings = zipWith downcast types polymorphicStrings

To connect with the question as asked: Exists Typeable is isomorphic to Dynamic. You might need to generalize Forall, Exists :: Constraint -> * to Forall, Exists :: [Constraint] -> * to comfortably support both IsString and Typeable at once, which is a bit of type-level hacking but nothing too strenuous. Type families can give you an Elem :: Constraint -> [Constraint] -> Bool which can be used to replace c ~ IsString everywhere above.

Upvotes: 4

Related Questions