Skip to content

Commit

Permalink
Implement pattern synonyms for StrictText and LazyText
Browse files Browse the repository at this point in the history
  • Loading branch information
Bodigrim committed Oct 20, 2024
1 parent d67f2aa commit ca115f5
Show file tree
Hide file tree
Showing 3 changed files with 64 additions and 0 deletions.
35 changes: 35 additions & 0 deletions src/Data/Text.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -Wno-partial-type-signatures #-}
Expand Down Expand Up @@ -61,6 +63,11 @@ module Data.Text
, singleton
, empty

-- * Pattern matching
, pattern Empty
, pattern (:<)
, pattern (:>)

-- * Basic interface
, cons
, snoc
Expand Down Expand Up @@ -565,6 +572,34 @@ null (Text _arr _off len) =
"TEXT null/empty -> True" null empty = True
#-}

-- | Bidirectional pattern synonym for 'empty' and 'null' (both /O(1)/),
-- to be used together with '(:<)' or '(:>)'.
--
-- @since 2.1.2
pattern Empty :: Text
pattern Empty <- (null -> True) where
Empty = empty

-- | Bidirectional pattern synonym for 'cons' (/O(n)/) and 'uncons' (/O(1)/),
-- to be used together with 'Empty'.
--
-- @since 2.1.2
pattern (:<) :: Char -> Text -> Text
pattern x :< xs <- (uncons -> Just (x, xs)) where
(:<) = cons
infixr 5 :<
{-# COMPLETE Empty, (:<) #-}

-- | Bidirectional pattern synonym for 'snoc' (/O(n)/) and 'unsnoc' (/O(1)/)
-- to be used together with 'Empty'.
--
-- @since 2.1.2
pattern (:>) :: Text -> Char -> Text
pattern xs :> x <- (unsnoc -> Just (xs, x)) where
(:>) = snoc
infixl 5 :>
{-# COMPLETE Empty, (:>) #-}

-- | /O(1)/ Tests whether a 'Text' contains exactly one character.
isSingleton :: Text -> Bool
isSingleton = S.isSingleton . stream
Expand Down
2 changes: 2 additions & 0 deletions src/Data/Text/Internal/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,9 @@ import qualified Data.Text.Internal as T
import qualified Data.Text as T

data Text = Empty
-- ^ Empty text.
| Chunk {-# UNPACK #-} !T.Text Text
-- ^ Chunks must be non-empty, this invariant is not checked.
deriving (Typeable)

-- | Type synonym for the lazy flavour of 'Text'.
Expand Down
27 changes: 27 additions & 0 deletions src/Data/Text/Lazy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- Module : Data.Text.Lazy
Expand Down Expand Up @@ -60,6 +62,11 @@ module Data.Text.Lazy
, foldrChunks
, foldlChunks

-- * Pattern matching
, pattern Empty
, pattern (:<)
, pattern (:>)

-- * Basic interface
, cons
, snoc
Expand Down Expand Up @@ -533,6 +540,26 @@ null Empty = True
null _ = False
{-# INLINE [1] null #-}

-- | Bidirectional pattern synonym for 'cons' (/O(n)/) and 'uncons' (/O(1)/),
-- to be used together with 'Empty'.
--
-- @since 2.1.2
pattern (:<) :: Char -> Text -> Text
pattern x :< xs <- (uncons -> Just (x, xs)) where
(:<) = cons
infixr 5 :<
{-# COMPLETE Empty, (:<) #-}

-- | Bidirectional pattern synonym for 'snoc' (/O(n)/) and 'unsnoc' (/O(1)/)
-- to be used together with 'Empty'.
--
-- @since 2.1.2
pattern (:>) :: Text -> Char -> Text
pattern xs :> x <- (unsnoc -> Just (xs, x)) where
(:>) = snoc
infixl 5 :>
{-# COMPLETE Empty, (:>) #-}

-- | /O(1)/ Tests whether a 'Text' contains exactly one character.
isSingleton :: Text -> Bool
isSingleton = S.isSingleton . stream
Expand Down

0 comments on commit ca115f5

Please sign in to comment.