user1892304
user1892304

Reputation: 637

How can I concisely match a list according to its latter half, and bind it's former half accordingly?

Suppose I have a function f :: String -> String and want to match arguments of the form

_ ++ "bar"

where _ is an unspecified string that I would like to return. In other words, I want to match arguments like foobar and bazbar and return foo and baz respectively.

Using ViewPatterns this is possible as follows:

{-# LANGUAGE ViewPatterns #-}

f :: String -> String
f x@(reverse . take 3 $ reverse -> "bar") = take (n-3) x
    where n = length x

...but this is far from ideal. Mainly because things will get hairy very quickly if I decide that I want to combine two or more such patterns.

Ideally, I want something to be able to write something like this:

f (x:"bar") = x

but unfortunately this is not valid Haskell.

Is there an adequate solution in ViewPatterns or another extension?

Upvotes: 2

Views: 87

Answers (4)

Isaac van Bakel
Isaac van Bakel

Reputation: 1862

This is almost possible with TemplateHaskell - someone more experienced with it could improve on this answer.

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

(+++) :: Q Pat -> String -> Q Pat
x +++ y = [p| ((\string -> splitAt (length string - length y) string) -> (x, $literal_pattern)) |]
  where literal_pattern = returnQ (LitP (StringL y))

This is usable in the pattern position, and you can pass in a pattern as the first argument using TemplateHaskell's quasiquoting:

f $([p|x|] +++ "bar") = x

Rather annoyingly, I can't find any explanation of how you can pass a pattern to a TemplateHaskell splice any more succintly than this.

Upvotes: 0

moonGoose
moonGoose

Reputation: 1510

stripSuffix :: (Eq a) => [a] -> [a] -> Maybe [a]
stripSuffix needle = go <*> drop (length needle)
  where
    go xs [] = if xs == needle then Just [] else Nothing
    go (x:xs) (_:ys) = (x:) <$> go xs ys

f (stripSuffix "bar" -> Just pref) = pref

I haven't tested it too much but this is a simple solution that doesn't bring in extra machinery of regexs / parsers.

Upvotes: 2

Alec
Alec

Reputation: 32319

On built-in String, this is a very bad idea, since your pattern match turns out to be quite expensive. On other string types, like Text or ByteString, you can use pattern guards:

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.Text as T

f :: Text -> Text
f x | Just x' <- T.stripSuffix "bar" x = ...

Or with ViewPatterns (of which I am less fond):

{-# LANGUAGE OverloadedStrings, ViewPatterns #-}

import qualified Data.Text as T

f :: Text -> Text
f (T.stripSuffix "bar" -> Just x') = ...

Upvotes: 3

amalloy
amalloy

Reputation: 92117

Don't do it with pattern matching. Pattern matches are typically cheap and match the structure of the input data. This is a very expensive pattern written as if it were very cheap to compute. If you want to do this, write it as a guard clause, where you can make it clear exactly what's happening.

Upvotes: 0

Related Questions