
Hi, I'm trying to generalize my string substitution library (http://hackage.haskell.org/package/template) to allow users to provide different kinds of key/value mappings (e.g. functions and association lists) for filling in the placeholders in a template. Here are two examples I'd like to work: ghci> :set -XOverloadedStrings ghci> "$name ate a banana." % [("name", "Johan")] "Johan ate a banana." ghci> "$name ate a banana." % (\v -> if v == "name" then "Johan" else error "KeyError") "Johan ate a banana." At the moment the context (i.e. the second argument to "%") is always a function type Context = T.Text -> T.Text I would like to generalize that to class Context a where lookup :: a -> T.Text -> T.Text Different key/value mappings fulfill different use cases: * Association lists have a small syntactic overhead, great for one-off string substitution. * Functions are flexible, allowing for arbitrary complex lookup logic, but are syntactically heavy (in this case.) Here's the gist of my implementation: {-# LANGUAGE FlexibleInstances #-} module Template where import Data.Maybe (fromMaybe) import qualified Data.Text as T import qualified Data.Text.Lazy as LT import Prelude as P class Context a where lookup :: a -> T.Text -> T.Text instance Context (T.Text -> T.Text) where lookup f = f instance Context [(T.Text, T.Text)] where lookup xs k = fromMaybe (error $ "KeyError: " ++ show k) (P.lookup k xs) -- | Perform string substitution. Example: -- -- > "$foo" % [("foo" :: T.Text, "bar" :: T.Text)] (%) :: Context c => T.Text -> c -> LT.Text (%) = undefined The problem is that the compiler is not able to deduce that string literals should have type 'Text' when used in 'Context's. For example ghci> :t "$foo" % [("foo", "bar")] <interactive>:1:8: No instance for (Context [(a, a1)]) arising from a use of `%' Possible fix: add an instance declaration for (Context [(a, a1)]) In the expression: "$foo" % [("foo", "bar")] This forces the user to provide explicit type signatures, which makes the construct more heavy weight and defeats the whole purpose of introducing the 'Context' class: ghci> :t "$foo" % [("foo" :: T.Text, "bar" :: T.Text)] "$foo" % [("foo" :: T.Text, "bar" :: T.Text)] :: LT.Text Is there any way to make the syntactically short `"$foo" % [("foo", "bar")]` work but still keep the 'Context' class? Johan