{-# LANGUAGE Trustworthy #-}

{- arch-tag: String utilities main file
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : Data.String.Utils
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

This module provides various helpful utilities for dealing with strings.

Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.String.Utils
                       (-- * Whitespace Removal
                        strip, lstrip, rstrip,
                        -- * Tests
                        -- | Note: These functions are aliases for functions
                        -- in "Data.List.Utils".
                        startswith, endswith,
                        -- * Conversions
                        -- | Note: Some of these functions are aliases for functions
                        -- in "Data.List.Utils".
                        join, split, splitWs, replace, escapeRe,
                        -- * Reading
                        maybeRead
                       ) where

import           Data.Char       (isAlpha, isAscii, isDigit)
import           Data.List.Utils (endswith, join, replace, split, startswith)
import           Data.Maybe      (listToMaybe)
import           Text.Regex      (mkRegex, splitRegex)

wschars :: String
wschars :: String
wschars = String
" \t\r\n"

{- | Removes any whitespace characters that are present at the start
or end of a string. Does not alter the internal contents of a
string. If no whitespace characters are present at the start or end
of a string, returns the original string unmodified. Safe to use on
any string.

Note that this may differ from some other similar
functions from other authors in that:

1. If multiple whitespace
characters are present all in a row, they are all removed;

2. If no
whitespace characters are present, nothing is done.
-}
strip :: String -> String
strip :: String -> String
strip = String -> String
lstrip (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
rstrip

-- | Same as 'strip', but applies only to the left side of the string.
lstrip :: String -> String
lstrip :: String -> String
lstrip String
s = case String
s of
                  [] -> []
                  (Char
x:String
xs) -> if Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem Char
x String
wschars
                            then String -> String
lstrip String
xs
                            else String
s

-- | Same as 'strip', but applies only to the right side of the string.
rstrip :: String -> String
rstrip :: String -> String
rstrip = String -> String
forall a. [a] -> [a]
reverse (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
lstrip (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
forall a. [a] -> [a]
reverse

{- | Splits a string around whitespace.  Empty elements in the result
list are automatically removed. -}
splitWs :: String -> [String]
splitWs :: String -> [String]
splitWs = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (\String
x -> String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= []) ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Regex -> String -> [String]
splitRegex (String -> Regex
mkRegex String
"[ \t\n\r\v\f]+")

{- | Escape all characters in the input pattern that are not alphanumeric.

Does not make special allowances for NULL, which isn't valid in a
Haskell regular expression pattern. -}
escapeRe :: String -> String
escapeRe :: String -> String
escapeRe [] = []
escapeRe (Char
x:String
xs)
    -- Chars that we never escape
    | Char
x Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'\'', Char
'`'] = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escapeRe String
xs
    -- General rules for chars we never escape
    | Char -> Bool
isDigit Char
x Bool -> Bool -> Bool
|| (Char -> Bool
isAscii Char
x Bool -> Bool -> Bool
&& Char -> Bool
isAlpha Char
x) Bool -> Bool -> Bool
|| Char
x Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'<', Char
'>']
        = Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escapeRe String
xs
    -- Escape everything else
    | Bool
otherwise = Char
'\\' Char -> String -> String
forall a. a -> [a] -> [a]
: Char
x Char -> String -> String
forall a. a -> [a] -> [a]
: String -> String
escapeRe String
xs

-- | Attempts to parse a value from the front of the string.
maybeRead :: Read a => String -> Maybe a
maybeRead :: forall a. Read a => String -> Maybe a
maybeRead = ((a, String) -> a) -> Maybe (a, String) -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (a, String) -> a
forall a b. (a, b) -> a
fst (Maybe (a, String) -> Maybe a)
-> (String -> Maybe (a, String)) -> String -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(a, String)] -> Maybe (a, String)
forall a. [a] -> Maybe a
listToMaybe ([(a, String)] -> Maybe (a, String))
-> (String -> [(a, String)]) -> String -> Maybe (a, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [(a, String)]
forall a. Read a => ReadS a
reads