GHC String Interpolation Survey - Final Results

Perhaps a more interesting example would be something with parsing:

data Scan a where
    ScanEnd :: Scan ()
    ScanInt :: Scan a -> Scan (Int, a)
    ScanLit :: String -> Scan a -> Scan a

instance Interpolate String (Scan a) (Scan a) where
    (%%) = ScanLit

instance Interpolate (Proxy Int) (Scan a) (Scan (Int, a)) where
    Proxy %% s = ScanInt s

evalScan :: Scan a -> String -> Maybe a
evalScan (ScanEnd) "" = Just ()
evalScan (ScanEnd) _ = Nothing
evalScan (ScanLit s rest) str = do
    str' <- stripPrefix s str
    evalScan rest str'
evalScan (ScanInt rest) str = do
    (x, str') <- case reads str of
        (x,str'):_ -> Just (x,str')
        _ -> Nothing
    r <- evalScan rest str'
    pure (x, r)

-- let str = "Age: 42"
-- (age, ()) <- Scan."Age: ${int}" str
1 Like

Sorry, yes, it is a bit of a wall of code.

By changing from a function that extracts the elements from a list, to a “joining” function, we allow each element in the list to have a different type (though, it doesn’t have to be, if your “joining” function is of type String -> String -> String, it does the expected).

But the power of being able to change the types as you go allows you to change the shape of the result based on the values you are interpolating.

In my two motivating examples above, when you interpolate a value of type Proxy a it creates a “slot” for a value of type a in the result. In the one case that “slot” is a a function argument, to be filled in later, and in the other example that “slot” is a place in a tuple that is returned by applying the Scan to a string.

EDIT:

The SQL example I provided is not highly motivating, because it’s fairly trivial to wrap it in a function:

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

Can just as well be written as:

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

But I think the scan example is slightly more motivating maybe?

EDIT2:

I see your response was not to my wall of code, sorry for the confusion.

Yeah, I like that. We shouldn’t hardcode lists into the interface. Let me include that

2 Likes

I just wanted to update my previous comment. The SQL example is useful, despite what I previously said. The reason I had it down as a motivational example is that, depending on the SQL engine, you might be able to pre-compile the parameterized query with the ? slots in place. Compare this to directly interpolating the values in, which means we can’t re-use it, and must re-compile the query every time those parameters change.

1 Like

One question about -XStringInterpolation with implicit-no-builder + -XQualifiedLiterals.

IIUC, it seems that we would have two ways of indicating interpolation: s"a ${x} b" when not using -XQualifiedLiterals and SomeModule."a ${x} b" when using -XQualifiedLiterals. I think I would prefer always using the module qualification mechanism instead .

-XQualifiedLiterals would enable qualifying string literals (and, in the future, numeric literals too) and the qualified module should define fromString, fromParts, and interpolate, injected at the appropriate places:

It seems that -XQualifiedLiterals could work as its own extension, without the need to define an Interpolate class at all (each module could potentially introduce its own mechanism for interpolate). I still don’t see the usefulness of expanding it to numeric literals though, as it seems a very string-interpolation focused extension. :thinking:

I’m a bit confused. What is -XQualifiedLiterals? Can someone point me to the proposal? The short text from the survey result doesn’t really tell me much.

Sure, you could choose to always use QualifiedLiterals, but then you’d have to write the interpolation code yourself. The s"..." syntax would be built into the language

Maybe a more motivating example is extending QualifiedLiterals to lists (analogous to OverloadedLists)?

fromList :: [a] -> Vector a
fromList = Vector.fromList

toList :: Vector a -> [a]
toList = Vector.toList

-- old way

V.fromList [1, 2, 3]

case maybeVector of
  Just v' | [_, v] <- Vector.toList v' -> ...
  _ -> ...

-- new way

V.[1, 2, 3]

case maybeVector of
  Just V.[_, v] -> ...
  _ -> ...
1 Like

QualifiedLiterals is a new extension I’m bundling with the StringInterpolation proposal. You can see its specification in the same proposal: Native string interpolation syntax by brandonchinn178 · Pull Request #570 · ghc-proposals/ghc-proposals · GitHub

1 Like

And that part is going to be voted on separately?

1 Like

extending QualifiedLiterals to lists

Ah, I see! I would personally prefer different extensions for different literal types, to avoid having to get them all “right” in one go. But perhaps the extensions would proliferate too much.

As for the s"a ${x} b" syntax, was using -XMagicHash considered as a possibility? Something like "a ${x} b"#s. -XMagicHash (and -XExtendedLiterals) already seem to be used to modify the behavior of literals.

-XMagicHash would play well with the proposed -XQualifiedLiterals, in that SomeModule."foo" would be a “normal” string and SomeModule."foo${bar}baz"#s would be an interpolated one (both according to the rules set in SomeModule).

I don’t think we have to get them all “right in one go”. We could start with strings and add num/lists/etc over time. The extension would just get more powerful each time, and remains backwards compatible

MagicHash is interesting, but IMO the string interpolation identifier should be at the start, to immediately indicate that this is interpolated, instead of waiting to the end. Also, I think it would be much more difficult to implement

It seems like this QualifiedLiterals idea would conflict with this ghc-proposal: Allow arbitrary identifiers as fields in `OverloadedRecordDot` and `OverloadedRecordUpdate` by parsonsmatt · Pull Request #668 · ghc-proposals/ghc-proposals · GitHub

For instance if we did:

import Data.Text (Text)
import qualified Data.Text as Text

foo = Text."foo"

That could either be a field accessor or a string interpolation.

I think this is a strong reason to prefer foo".." where foo is an identifier of an appropriate type rather than using module qualification.
Also if you use identifiers you would benefit from HLS’s ability to “jump to definition”. Something like that wouldn’t make sense for the module qualified version as there would be no one location to jump to.

In general, I get the sense that this idea is mostly just useful for string interpolation. I’m not sure if the other literals need this generality. So it might be good to refocus this as just a QualifiedStringInterpolation thing.

I don’t have a clear opinion on qualified literals, but I don’t think the conflict with OverloadedRecordDot is a hard blocker. Text.foo is already considered to be a qualified name rather than a field accessor, and treating Text."foo" similarly would hardly be unreasonable. After all, nullary data constructors don’t usually have fields!

2 Likes

Broke out a proposal for QualifiedLiterals: QualifiedLiterals by brandonchinn178 · Pull Request #698 · ghc-proposals/ghc-proposals · GitHub

@hasufell I know you have lots of thoughts on IsString + ByteString + OSPath. I’d appreciate a quick look from you and see if there’s anything you find interesting

4 Likes