{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Regex.KDE.Regex
 ( Direction(..)
 , Regex(..)
 , isWordChar
 ) where

import Data.Char
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup ((<>), Semigroup)
#endif

data Direction = Forward | Backward
  deriving (Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Direction] -> ShowS
$cshowList :: [Direction] -> ShowS
show :: Direction -> String
$cshow :: Direction -> String
showsPrec :: Int -> Direction -> ShowS
$cshowsPrec :: Int -> Direction -> ShowS
Show, Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c== :: Direction -> Direction -> Bool
Eq)

data Regex =
  MatchAnyChar |
  MatchDynamic !Int |
  MatchChar (Char -> Bool) |
  MatchSome !Regex |
  MatchAlt !Regex !Regex |
  MatchConcat !Regex !Regex |
  MatchCapture !Int !Regex |
  MatchCaptured !Int |
  AssertWordBoundary |
  AssertBeginning |
  AssertEnd |
  AssertPositive !Direction !Regex |
  AssertNegative !Direction !Regex |
  Possessive !Regex |
  Lazy !Regex |
  Recurse |
  MatchNull

instance Show Regex where
  show :: Regex -> String
show Regex
MatchAnyChar = String
"MatchAnyChar"
  show (MatchDynamic Int
i) = String
"MatchDynamic " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
i
  show (MatchChar Char -> Bool
_) = String
"(MatchChar <fn>)"
  show (MatchSome Regex
re) = String
"(MatchSome " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (MatchAlt Regex
r1 Regex
r2) = String
"(MatchAlt " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
r1 String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
r2 String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (MatchConcat Regex
r1 Regex
r2) = String
"(MatchConcat " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
r1 String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
r2 String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
            String
")"
  show (MatchCapture Int
i Regex
re) = String
"(MatchCapture " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
i String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
                Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (MatchCaptured Int
n) = String
"(MatchCaptured " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Int -> String
forall a. Show a => a -> String
show Int
n String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show Regex
AssertWordBoundary = String
"AssertWordBoundary"
  show Regex
AssertBeginning = String
"AssertBeginning"
  show Regex
AssertEnd = String
"AssertEnd"
  show (AssertPositive Direction
dir Regex
re) = String
"(AssertPositive " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Direction -> String
forall a. Show a => a -> String
show Direction
dir String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
                  Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (AssertNegative Direction
dir Regex
re) = String
"(AssertNegativeLookahead " String -> ShowS
forall a. Semigroup a => a -> a -> a
<>
                  Direction -> String
forall a. Show a => a -> String
show Direction
dir String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (Possessive Regex
re) = String
"(Possessive " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show (Lazy Regex
re) = String
"(Lazy " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Regex -> String
forall a. Show a => a -> String
show Regex
re String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
")"
  show Regex
Recurse = String
"Recurse"
  show Regex
MatchNull = String
"MatchNull"

instance Semigroup Regex where
  <> :: Regex -> Regex -> Regex
(<>) = Regex -> Regex -> Regex
MatchConcat

instance Monoid Regex where
  mempty :: Regex
mempty = Regex
MatchNull
  mappend :: Regex -> Regex -> Regex
mappend = Regex -> Regex -> Regex
forall a. Semigroup a => a -> a -> a
(<>)

isWordChar :: Char -> Bool
isWordChar :: Char -> Bool
isWordChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char -> GeneralCategory
generalCategory Char
c GeneralCategory -> GeneralCategory -> Bool
forall a. Eq a => a -> a -> Bool
== GeneralCategory
ConnectorPunctuation