{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE Safe #-}
module Kleene.Internal.Functor (
K (..),
Greediness (..),
few,
anyChar,
oneof,
char,
charRange,
dot,
everything,
everything1,
isEmpty,
isEverything,
match,
toRE,
toKleene,
fromRE,
toRA,
) where
import Prelude ()
import Prelude.Compat
import Control.Applicative (Alternative (..), liftA2)
import Data.Foldable (toList)
import Data.Functor.Apply (Apply (..))
import Data.RangeSet.Map (RSet)
import Data.String (IsString (..))
import qualified Data.RangeSet.Map as RSet
import qualified Text.Regex.Applicative as R
import qualified Data.Functor.Alt as Alt
import qualified Kleene.Classes as C
import Kleene.Internal.Pretty
import Kleene.Internal.Sets
import qualified Kleene.RE as RE
data Greediness
= Greedy
| NonGreedy
deriving (Eq, Ord, Show, Enum, Bounded)
data K c a where
KEmpty :: K c a
KPure :: a -> K c a
KChar :: (Ord c, Enum c) => RSet c -> K c c
KAppend :: (a -> b -> r) -> K c a -> K c b -> K c r
KUnion :: K c a -> K c a -> K c a
KStar :: Greediness -> K c a -> K c [a]
KMap :: (a -> b) -> K c a -> K c b
KString :: Eq c => [c] -> K c [c]
instance (c ~ Char, IsString a) => IsString (K c a) where
fromString s = KMap fromString (KString s)
instance Functor (K c) where
fmap _ KEmpty = KEmpty
fmap f (KPure x) = KPure (f x)
fmap f (KMap g k) = KMap (f . g) k
fmap f (KAppend g a b) = KAppend (\x y -> f (g x y)) a b
fmap f k = KMap f k
instance Apply (K c) where
KEmpty <.> _ = KEmpty
_ <.> KEmpty = KEmpty
KPure f <.> k = fmap f k
k <.> KPure x = fmap ($ x) k
f <.> x = KAppend ($) f x
liftF2 = KAppend
instance Applicative (K c) where
pure = KPure
(<*>) = (<.>)
#if MIN_VERSION_base(4,10,0)
liftA2 = liftF2
#endif
instance Alt.Alt (K c) where
KEmpty <!> k = k
k <!> KEmpty = k
KChar a <!> KChar b = KChar (RSet.union a b)
a <!> b = KUnion a b
many KEmpty = KPure []
many (KStar _ k) = KMap pure (KStar Greedy k)
many k = KStar Greedy k
some KEmpty = KEmpty
some (KStar _ k) = KMap pure (KStar Greedy k)
some k = liftA2 (:) k (KStar Greedy k)
instance Alternative (K c) where
empty = KEmpty
(<|>) = (Alt.<!>)
some = Alt.some
many = Alt.many
few :: K c a -> K c [a]
few KEmpty = KPure []
few (KStar _ k) = KMap pure (KStar NonGreedy k)
few k = KStar NonGreedy k
anyChar :: (Ord c, Enum c, Bounded c) => K c c
anyChar = KChar RSet.full
oneof :: (Ord c, Enum c, Foldable f) => f c -> K c c
oneof = KChar . RSet.fromList . toList
char :: (Ord c, Enum c) => c -> K c c
char = KChar . RSet.singleton
charRange :: (Enum c, Ord c) => c -> c -> K c c
charRange a b = KChar (RSet.singletonRange (a, b))
dot :: K Char Char
dot = KChar dotRSet
everything :: (Ord c, Enum c, Bounded c) => K c [c]
everything = many anyChar
everything1 :: (Ord c, Enum c, Bounded c) => K c [c]
everything1 = some anyChar
isEmpty :: (Ord c, Enum c, Bounded c) => K c a -> Bool
isEmpty k = C.equivalent (toRE k) C.empty
isEverything :: (Ord c, Enum c, Bounded c) => K c a -> Bool
isEverything k = C.equivalent (toRE k) C.everything
match :: K c a -> [c] -> Maybe a
match = R.match . toRA
toRE :: (Ord c, Enum c, Bounded c) => K c a -> RE.RE c
toRE = toKleene
toKleene :: C.FiniteKleene c k => K c a -> k
toKleene (KMap _ a) = toKleene a
toKleene (KUnion a b) = C.unions [toKleene a, toKleene b]
toKleene (KAppend _ a b) = C.appends [toKleene a, toKleene b]
toKleene (KStar _ a) = C.star (toKleene a)
toKleene (KString s) = C.appends (map C.char s)
toKleene KEmpty = C.empty
toKleene (KPure _) = C.eps
toKleene (KChar cs) = C.fromRSet cs
fromRE :: (Ord c, Enum c) => RE.RE c -> K c [c]
fromRE (RE.REChars cs) = pure <$> KChar cs
fromRE (RE.REAppend rs) = concat <$> traverse fromRE rs
fromRE (RE.REUnion cs rs) = foldr (KUnion . fromRE) (pure <$> KChar cs) (toList rs)
fromRE (RE.REStar r) = concat <$> KStar Greedy (fromRE r)
toRA :: K c a -> R.RE c a
toRA KEmpty = empty
toRA (KPure x) = pure x
toRA (KChar cs) = R.psym (\c -> RSet.member c cs)
toRA (KAppend f a b) = liftA2 f (toRA a) (toRA b)
toRA (KUnion a b) = toRA a <|> toRA b
toRA (KStar Greedy a) = many (toRA a)
toRA (KStar NonGreedy a) = R.few (toRA a)
toRA (KMap f a) = fmap f (toRA a)
toRA (KString s) = R.string s
instance c ~ Char => Pretty (K c a) where
pretty = pretty . toRE