GHC String Interpolation Survey - Final Results

Apologies for the many, many posts, but this will be the last one. We made it.

Without further ado, results can be found here: GHC String Interpolation Survey Results. Scroll down to the “Commentary” section.

I’m really excited about the hybrid solution that came out of this process; I think this will truly be the best of all the worlds. A tremendous thank you to everyone who participated, I think we’ve definitely come out of this with a much stronger proposal than what I started with.

Feel free to post comments/questions in this thread, I will respond to what I can. But no matter what, I promise that there will be no more surveys :slightly_smiling_face: I will update the proposal when I can get to it, so subscribe there for further updates.

23 Likes

Thanks for all your work on this!

3 Likes

I’ve often wanted something like -XQualifiedLiterals by itself! Although I would probably call it -XQualifiedStringLiterals.

Thanks for all your work on this!

The final suggestions you have with both -XStringInterpolation and -XQualifiedLiterals sounds great to me and I love the overall design. I found the SQL example intuitive at a glance, even before I read any of the explanation for it:

SQL."select * from users where name = ${name}"
2 Likes

Thanks for running this! I’m not terribly surprised to see that nobody except me likes explicit, but I’m glad we checked!

1 Like

I was the other person that liked explicit then, I guess :upside_down_face:
But I’m not discontent with the results.

Just a sidenote: the result also means that OsPath will not work with this, because it does not have an IsString instance: GitHub · Where software is built

It should work with the new QualifiedLiterals extension proposed in the results?

module System.OsPath.Interpolate where

fromParts :: [String] -> Maybe OsPath
fromParts = encodeUtf . concat

fromString :: String -> String
fromString = id

-- reusing String's Interpolate instances as an example;
-- the signature here could be anything
interpolate :: Interpolate a String => a -> String
interpolate = show
{-# LANGUAGE QualifiedLiterals #-}

import System.OsPath.Interpolate qualified as OsPath

main = do
  let user = "testuser"
  print OsPath."/home/${user}/foo.txt"
  -- Just "/home/testuser/foo.txt"
1 Like

Why does the QualifiedLiterals idea require qualifying things by modules? As far as I can tell something like foo"..." should work where foo is a record of the appropriate type. This is how Quasiquotes work

1 Like

Now I come to think of it, why does QualifiedDo? It could also technically work as var.do, where var is a variable whose type is a record containing the desired Monad operations. Perhaps the parser would have a hard time, especially when OverloadedRecordDot is in play.

1 Like

Sure, that would work too. But the QualifiedLiterals approach has two advantages:

  • It removes whitespace ambiguity (Foo."..." is invalid syntax right now, while foo"..." is a function application)
  • QualifiedLiterals is extendable to numeric literals

Conceptually, I also like the consistency with QualifiedDo; foo"..." would be yet another syntactic structure added to the language.

2 Likes

It removes a possibility: you can’t determine the interpolation function at run time. I’m not sure that feature would be used in practice, but it seems unfortunate to close it off unless absolutely necessary.

That possibility seems little better than explicitly calling the interpolation function.

Why doesn’t that argument apply to statically-determined interpolation functions too?

For my taste, using the module name would be more direct and understandable than trying to puzzle out the provenance of a value that guides interpolation. Worth the loss in flexibility, especially considering that the implementation would be simpler.

Also, IIUC, the interpolation should work for a potentially open set of value types, so I’m not sure how the record carrying the interpolation functions for each type would work.

And if I wanted to use -XQualifiedLiterals on its own as an alternative to -XOverloadedStrings (say, be able to write T."foo" to build a Text) the more flexible approach would be overkill.

Im also happy with the simpler default interpolation put together with QualifiedLiterals. Good idea.

Do you have a use-case in mind?

You could get similar behavior with a custom interpolator

module MyInterpolate where

str1 :: [Either String Val] -> String
str2 :: [Either String Val] -> String

fromParts = id
fromString = Left
interpolate :: Val -> Either String Val
interpolate = Right

data Val = I Int | S String
import MyInterpolate qualified as I

main = do
  let str = if ... then str1 else str2
  putStrLn $ str $ I."..."
2 Likes

No , I don’t have a use case in mind, I just didn’t want to close off a possibility unnecessarily (Haskell has benefitted a lot historically from this kind of approach.)

Ah yes, OK, perhaps if you define an interpretation that’s “open” in some sense (or maybe “initial”?) then you can handle it however you want after the fact.

1 Like

Ok, I hate to toss this in so late, but, the fromParts is essentially a Monoid like interface. So, it could be broken up into a mempty/<> pair. If we did this, we would also have the option of allowing the <> type to change the type of the result as we go (no longer a true monoid).

My motivation here is to allow for the types to change as we construct the value, which has the benefits of allowing some interesting patterns (e.g. returning functions).

A simple demonstration, I’ve called the functions %% and final, as well as introducing an extract function:

{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE GADTs #-}

-- Data.Printf.Interpolate
-- defines `%%`, `extract` and `final`
import Data.Proxy

-- Represents a string literal, as opposed to a string that should be interpolated.
newtype Lit = Lit String

infixr 5 %%
class Interpolate a b c | a c -> b where
    (%%) :: a -> b -> c

data Printf a where
    PrintfEnd  :: Printf String
    PrintfLit  :: String -> Printf a -> Printf a
    PrintfArg  :: Show b => Printf a -> Printf (b -> a)

final :: Printf String
final = PrintfEnd

instance Interpolate Lit (Printf a) (Printf a) where
    Lit s %% p = PrintfLit s p

instance Interpolate String (Printf a) (Printf a) where
    s %% p = PrintfLit s p

instance Interpolate (Proxy Int) (Printf a) (Printf (Int -> a)) where
    Proxy %% p = PrintfArg p

instance Interpolate (Proxy Float) (Printf a) (Printf (Float -> a)) where
    Proxy %% p = PrintfArg p

instance Interpolate Int (Printf a) (Printf a) where
    x %% p = PrintfLit (show x) p

evalPrintf' :: Printf a -> (String -> String) -> a
evalPrintf' PrintfEnd f = f ""
evalPrintf' (PrintfLit s p) f = evalPrintf' p ((++s) . f)
evalPrintf' (PrintfArg p) f = \x -> evalPrintf' p ((++ show x) . f)

extract :: Printf a -> a
extract p = evalPrintf' p id

int :: Proxy Int
int = Proxy

float :: Proxy Float
float = Proxy

x :: Int
x = 3

y :: Int
y = 5

z :: Float
z = 3.2

-- Usage:
-- Printf."Example ${x} ${int} ${float}" y z
-- desugars to
res = extract (Lit "Example " %% x %% Lit " " %% int %% Lit " " %% float %% final) y z
-- "Example 3 5 3.2"

-- Or consider possibilities like
-- getNameForPerson :: PersonId -> IO String
-- getNameForPerson = SQL."select name from people where id is ${personid}"

Note how the Printf example above supports both interpolating the x into the string directly, as well as leaving other parameters to be supplied as arguments to the resulting function.

I haven’t really considered any performance or type-error ergonomics issues this may present yet.

2 Likes

Goodness… @brandonchinn178: sorry to be that person, but I have literally no idea what the conclusion of the results is: could you pretty please add a TL;DR at the top or in this thread at least? :slight_smile:

2 Likes