It’s been a bit since I’ve posted an update, and I thought now would be a good time as any to re-poke the community for thoughts.
-XQualifiedStrings
First of all, QualifiedStrings has been accepted! Implementation is ready for review, so we should hopefully see it in GHC 9.16. This extension enables locally-scoped OverloadedStrings:
{-# LANGUAGE QualifiedStrings #-}
import qualified Data.Text.Qualified as T
import qualified Data.ByteString.Qualified.Utf8 as Utf8
"asdf" -- String
T."asdf" -- Text
Utf8."asdf" -- ByteString
There are other qualified-literals proposals up as well (QualifiedLists, QualifiedNumerics), but those seem more controversial and require additional discussion. If you’re interested, take a look and leave comments!
-XStringInterpolation
With QualifiedStrings accepted, the StringInterpolation proposal has been revamped into a very simple implementation, plus a qualified-interpolation for use-cases needing more power.
{-# LANGUAGE StringInterpolation #-}
s"a ${x} b"
-- Desugars to:
interpolateString $ \convert raw append empty ->
raw "a "
`append` convert x
`append` raw " b"
`append` empty
-- Provided by Data.String.Interpolate:
interpolateString :: (IsString s, Monoid s) => ...
interpolateString f = mconcat $ f (fromString . interpolate) id (:) []
class Interpolate a where
{-# MINIMAL interpolate | interpolateS #-}
interpolate :: a -> String
interpolateS :: a -> ShowS
{-# LANGUAGE QualifiedStrings #-}
{-# LANGUAGE StringInterpolation #-}
import qualified Data.SQL as SQL
SQL.s"SELECT * FROM users WHERE name = ${name}"
-- Defined in Data.SQL:
interpolateString :: ((forall a. ToSqlValue a => a -> SqlQuery) -> ...) -> SqlQuery
interpolateString f = mconcat $ f toSqlValue fromString mappend mempty
Please take a look and leave comments! We need more input from folks to find a solution that the community is satisfied with.
Per QualifiedStrings, I do understand that we must use namespaces as sigils / prefixes (eg, Text."utf8" instead of u"utf8") in order to remain extensible without affecting Haskell’s syntax / grammar, its just that I find that path a little overused (awkward?) eg, using qualified namespaces to scope / control things that other languages have syntactic support for (instead of overloading the namespace operator for it). I have strong feelings about this, I don’t like the syntax (note, I don’t necessarily dislike it either) because its turning Haskell’s (already weak) modules into something more complicated and because now you also have to know whether the imported module supports QualifiedStrings, but I do not have an alternative that is as low-hanging as this so eh.
Warty when considered alone, but on the other hand, I already have to do this with qualified types, and the other QualifiedFoo proposals maybe we will at least make this… consistent. If we do embrace this pattern, maybe we really do need better ergonomics on importing qualified things that support module- / import-level shenanigans though.
With respect to the latter StringInterpolation, I agree that it is a hard swallow coming from Haskell’s tendency towards a purist perspective; however this feature is common in many other languages, so it is not unfamiliar, and it is syntax sugar so it is no more ‘out there’ than things like ImplicitParams. I know, slight chagrin and irony given my reaction to the former.
To that regard, even if the proposal for it does not get approved (or, approved now because the utility (eg improved readability) of this is high enough that I would expect it to be eventually revisited since even C has string interpolation via sprintf), I find this work to be highly valuable.
I haven’t read the proposal in detail nor really followed the discussion, but is there some explanation for why QualifiedStrings is better than
import qualified Data.Text.Qualified as T
import qualified Data.ByteString.Qualified.Utf8 as Utf8
"asdf" -- String
T.s "asdf" -- Text
Utf8.s "asdf" -- ByteString
(or choose your own favourite identifier other than s)?
QualifiedDo makes a lot of sense to me, because you get access to a special syntax by rebinding >>= and >>, but you don’t get a better syntax with QualifiedStrings. Compared to my suggestion above you just save “s “. Am I missing something?
Yeah, good question. The first thing is that qualified strings works in pattern matching too, which would be a bit more verbose than just two extra characters.
But philosophically, I’d ask what the point of OverloadedStrings was in the first place. You could make the same argument that it’s redundant if everyone just defines their own s function. But it’s nice ergonomically to just write a string literal and not add parentheses if it’s nested in an expression. QualifiedStrings has the same motivations as OverloadedStrings.
Furthermore, IMO, QualifiedStrings should supercede OverloadedStrings. OverloadedStrings is enabled globally and can introduce type ambiguity, and QualifiedStrings solves that. It also paves the way (alongside QualifiedDo) for local modules in Haskell, if we wanted to keep moving in that direction.
Yes, that’s nice. `M."asdf"`is significantly more pleasant than ((== M.fromString "asdf") -> True). (example from the proposal)
I suppose so. Personally I wouldn’t pay the cost of complicating the grammar for that, but I’m also the kind of person who’s sceptical of BlockArguments so take that with a pinch of salt.
It may not surprise you that I am no fan of OverloadedStrings! I certainly think QualifiedStringsis a better design (although personally I would prefer "StringLiteralsAreText”).
That sounds very cool!
EDIT: The pattern feature actually makes me wonder about a missing feature in PatternSynonymsin general: make them able to depend on values. For example, what I’d really like to do is this:
module T where
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
newtype X = X String
s :: String -> X
s = X
pattern S x <- x@((\y -> (s y ==)) -> True) where
S s = X s
then I could do let myString = S “Hello” in … and case … of S “Hello” → …. Crucially, the x field of the pattern S definition above would need to stand for expressions, not for patterns. I don’t know if that is remotely feasible, or if anyone has thought about extensions of PatternSynonyms.
But philosophically, I’d ask what the point of OverloadedStrings was in the first place.
To steal the prime syntactic real estate from the [Char] and help with the transition to something sane.
Unless QualifiedStrings somehow enables using ““ for Text then it can’t supercede it.
Text.interpolateString $ \_ raw _ _ -> raw "hello world"
?
Another question about StringInterpolation + QualifiedStrings. It seems that the combination would allow something that StringInterpolation by itself doesn’t seem to allow: that the intermediate values can be of a different type to that of the final result “string”. For example, it seems we could have a signature like
interpolateString ::
( (forall a. ToBuilder a => a → Builder)
→ (String → Builder)
→ (Builder → Builder → Builder)
→ Builder
→ Builder
)
→ Text
Yes, you’re right, I’ll update the proposal! Thanks
Yes! And that’s the key power behind qualified strings + qualified string interpolations - as long as the call-site compiles, the module can implement interpolateString however it wants, the same as QualifiedDo works with anything as long as it typechecks after desugaring.
Although note that your particular example of using Builder shouldn’t be necessary in most cases. The default interpolateString implementation will use mconcat, which is linear for Text. It might have performance benefits if you have a lot of nested values, but I still didn’t see any issues in my benchmarks
This reminds me of an interesting pattern matching option available in Scala, where you can bind identifiers from an interpolation. That is, you can write
str match {
case "hello" => "goodbye"
case s"my name is $name" => name
case s"https://$host/$path" => s"Hostname: $host, Path: $path"
case _ => "foo"
}
I can’t say I’ve used it, much, but there have been a few occasions where it was convenient to define my own StringContext (basically what the QualifiedStrings + StringInterpolation interaction amounts to) to enable fancy pattern matching on things that look like strings.
An interesting thing about this is that QualifiedStrings + Statically Checked Overloaded Strings might allow for StringInterpolation without an extension. The string interpolation would definitely be heavy weight though. But beyond StringInterpolation, combining the two techniques would also allow for just running TH in a nicer way.
I think this really warrants further consideration. If we could get bidirectional string patterns instead of just interpolation, that would be a nicely symmetric feature. It might also lead to clearer interpolation syntax than the not-quite-function-application that’s being proposed right now.
(Personally, I think formatting is a fantastic package that solves the interpolation problem in a Haskelly way. I don’t think it would have been developed if we had interpolation from the start.)
I’m going on a bit of a tangent here. One small dissatisfaction I had with the current design for the Interpolate class is that it only renders to String:
class Interpolate a where
{-# MINIMAL interpolate | interpolateS #-}
interpolate :: a -> String
interpolate x = interpolateS x ""
interpolateS :: a -> ShowS
interpolateS x s = interpolate x <> s
If we are generating a Text by interpolation, and the value we interpolate has a perfectly valid fooToText function somewhere, rendering it to a String and then to Text feels awkward (and perhaps inefficient, although I doubt the hit will be noticeable in most cases).
And yet, moving to a multi-parameter Interpolate a s typeclass would be awkward as well. We would have an explosion of instances that would be largely doing the same thing for a given a (they should generate similar strings).
I decided to play with rewrite rules to remove the intermediate String generation when we are rendering to Text. The idea is adding, for each type Foo that we may want to Interpolate, a rewrite rule of the form:
As the author I must admit that I’ve not used formatting for years after deciding it’s pointless in Haskell, and detrimental due to being position dependent.
I think printf, as a pattern, is the kind of thing that some languages need, like ones that are fussy about references and allocation like C, but Haskell isn’t one of those.
Haskell already has “foo” <> show x <> “bar” which is imho sufficiently snappy and flexible, and best of all you see the expression you’re “interpolating” in the place it’s “interpolated.”
That said, I’m sad because I love the mechanism that makes formatting work.
I do think there’s value in multi line quotes with interpolation for embedding other languages verbatim like in devops or something, though.
hm you’re right. Looking through the source code in text, I can’t find any rewrite rules for pack . unpack === id; the docs mention that unpack . pack is not necessarily id, but I don’t see a reasoning for pack . unpack. @Bodigrim is there a reason there isn’t a rewrite rule for pack (unpack s) = s?
I don’t really remember, it might be an accidental omission, or an artefact of disabling streaming fusion. Also it’s not quite identity: if s is a small chunk of a huge ByteArray, one might hope that pack . unpack will effectively clone the chunk and free the original ByteArray.
Overall I don’t believe that relying on rewrite rules for fundamental optimizations is a wise strategy.
Sorry, I didn’t follow https://github.com/ghc-proposals/ghc-proposals/pull/570 in detail. I’m sure it’s been bikesheded to death, but interpolate :: a -> String sounds too bad to be salvageable. Am I missing some trickery?