{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
module Data.Char.Brackets
(
bracketMaps,
brackets,
openBrackets,
closeBrackets,
toOpen,
toClose,
BracketType (Open, Close),
isBracket,
bracketType,
bracketType',
isOpenBracket,
isCloseBracket,
getOppositeChar,
getOppositeChar',
)
where
import Control.Applicative ((<|>))
import Control.DeepSeq (NFData)
import Data.Data (Data)
import Data.Hashable (Hashable)
import Data.Map (Map, fromList, lookup, member)
import Data.Maybe (fromMaybe)
import Data.Tuple (swap)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
import Prelude hiding (lookup)
data BracketType
=
Open
|
Close
deriving (BracketType
BracketType -> BracketType -> Bounded BracketType
forall a. a -> a -> Bounded a
$cminBound :: BracketType
minBound :: BracketType
$cmaxBound :: BracketType
maxBound :: BracketType
Bounded, Typeable BracketType
Typeable BracketType
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BracketType -> c BracketType)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BracketType)
-> (BracketType -> Constr)
-> (BracketType -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BracketType))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BracketType))
-> ((forall b. Data b => b -> b) -> BracketType -> BracketType)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r)
-> (forall u. (forall d. Data d => d -> u) -> BracketType -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> BracketType -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType)
-> Data BracketType
BracketType -> Constr
BracketType -> DataType
(forall b. Data b => b -> b) -> BracketType -> BracketType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> BracketType -> u
forall u. (forall d. Data d => d -> u) -> BracketType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BracketType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BracketType -> c BracketType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BracketType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BracketType)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BracketType -> c BracketType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BracketType -> c BracketType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BracketType
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c BracketType
$ctoConstr :: BracketType -> Constr
toConstr :: BracketType -> Constr
$cdataTypeOf :: BracketType -> DataType
dataTypeOf :: BracketType -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BracketType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c BracketType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BracketType)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c BracketType)
$cgmapT :: (forall b. Data b => b -> b) -> BracketType -> BracketType
gmapT :: (forall b. Data b => b -> b) -> BracketType -> BracketType
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BracketType -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> BracketType -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> BracketType -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BracketType -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> BracketType -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> BracketType -> m BracketType
Data, Int -> BracketType
BracketType -> Int
BracketType -> [BracketType]
BracketType -> BracketType
BracketType -> BracketType -> [BracketType]
BracketType -> BracketType -> BracketType -> [BracketType]
(BracketType -> BracketType)
-> (BracketType -> BracketType)
-> (Int -> BracketType)
-> (BracketType -> Int)
-> (BracketType -> [BracketType])
-> (BracketType -> BracketType -> [BracketType])
-> (BracketType -> BracketType -> [BracketType])
-> (BracketType -> BracketType -> BracketType -> [BracketType])
-> Enum BracketType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: BracketType -> BracketType
succ :: BracketType -> BracketType
$cpred :: BracketType -> BracketType
pred :: BracketType -> BracketType
$ctoEnum :: Int -> BracketType
toEnum :: Int -> BracketType
$cfromEnum :: BracketType -> Int
fromEnum :: BracketType -> Int
$cenumFrom :: BracketType -> [BracketType]
enumFrom :: BracketType -> [BracketType]
$cenumFromThen :: BracketType -> BracketType -> [BracketType]
enumFromThen :: BracketType -> BracketType -> [BracketType]
$cenumFromTo :: BracketType -> BracketType -> [BracketType]
enumFromTo :: BracketType -> BracketType -> [BracketType]
$cenumFromThenTo :: BracketType -> BracketType -> BracketType -> [BracketType]
enumFromThenTo :: BracketType -> BracketType -> BracketType -> [BracketType]
Enum, BracketType -> BracketType -> Bool
(BracketType -> BracketType -> Bool)
-> (BracketType -> BracketType -> Bool) -> Eq BracketType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BracketType -> BracketType -> Bool
== :: BracketType -> BracketType -> Bool
$c/= :: BracketType -> BracketType -> Bool
/= :: BracketType -> BracketType -> Bool
Eq, (forall x. BracketType -> Rep BracketType x)
-> (forall x. Rep BracketType x -> BracketType)
-> Generic BracketType
forall x. Rep BracketType x -> BracketType
forall x. BracketType -> Rep BracketType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BracketType -> Rep BracketType x
from :: forall x. BracketType -> Rep BracketType x
$cto :: forall x. Rep BracketType x -> BracketType
to :: forall x. Rep BracketType x -> BracketType
Generic, Eq BracketType
Eq BracketType
-> (BracketType -> BracketType -> Ordering)
-> (BracketType -> BracketType -> Bool)
-> (BracketType -> BracketType -> Bool)
-> (BracketType -> BracketType -> Bool)
-> (BracketType -> BracketType -> Bool)
-> (BracketType -> BracketType -> BracketType)
-> (BracketType -> BracketType -> BracketType)
-> Ord BracketType
BracketType -> BracketType -> Bool
BracketType -> BracketType -> Ordering
BracketType -> BracketType -> BracketType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BracketType -> BracketType -> Ordering
compare :: BracketType -> BracketType -> Ordering
$c< :: BracketType -> BracketType -> Bool
< :: BracketType -> BracketType -> Bool
$c<= :: BracketType -> BracketType -> Bool
<= :: BracketType -> BracketType -> Bool
$c> :: BracketType -> BracketType -> Bool
> :: BracketType -> BracketType -> Bool
$c>= :: BracketType -> BracketType -> Bool
>= :: BracketType -> BracketType -> Bool
$cmax :: BracketType -> BracketType -> BracketType
max :: BracketType -> BracketType -> BracketType
$cmin :: BracketType -> BracketType -> BracketType
min :: BracketType -> BracketType -> BracketType
Ord, ReadPrec [BracketType]
ReadPrec BracketType
Int -> ReadS BracketType
ReadS [BracketType]
(Int -> ReadS BracketType)
-> ReadS [BracketType]
-> ReadPrec BracketType
-> ReadPrec [BracketType]
-> Read BracketType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BracketType
readsPrec :: Int -> ReadS BracketType
$creadList :: ReadS [BracketType]
readList :: ReadS [BracketType]
$creadPrec :: ReadPrec BracketType
readPrec :: ReadPrec BracketType
$creadListPrec :: ReadPrec [BracketType]
readListPrec :: ReadPrec [BracketType]
Read, Int -> BracketType -> ShowS
[BracketType] -> ShowS
BracketType -> String
(Int -> BracketType -> ShowS)
-> (BracketType -> String)
-> ([BracketType] -> ShowS)
-> Show BracketType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BracketType -> ShowS
showsPrec :: Int -> BracketType -> ShowS
$cshow :: BracketType -> String
show :: BracketType -> String
$cshowList :: [BracketType] -> ShowS
showList :: [BracketType] -> ShowS
Show)
instance Arbitrary BracketType where
arbitrary :: Gen BracketType
arbitrary = Gen BracketType
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Hashable BracketType
instance NFData BracketType
bracketMaps :: [(Char, Char)]
bracketMaps :: [(Char, Char)]
bracketMaps =
[ (Char
'(', Char
')'),
(Char
'[', Char
']'),
(Char
'{', Char
'}'),
(Char
'\x0f3a', Char
'\x0f3b'),
(Char
'\x0f3c', Char
'\x0f3d'),
(Char
'\x169b', Char
'\x169c'),
(Char
'\x2045', Char
'\x2046'),
(Char
'\x207d', Char
'\x207e'),
(Char
'\x208d', Char
'\x208e'),
(Char
'\x2308', Char
'\x2309'),
(Char
'\x230a', Char
'\x230b'),
(Char
'\x2329', Char
'\x232a'),
(Char
'\x2768', Char
'\x2769'),
(Char
'\x276a', Char
'\x276b'),
(Char
'\x276c', Char
'\x276d'),
(Char
'\x276e', Char
'\x276f'),
(Char
'\x2770', Char
'\x2771'),
(Char
'\x2772', Char
'\x2773'),
(Char
'\x2774', Char
'\x2775'),
(Char
'\x27c5', Char
'\x27c6'),
(Char
'\x27e6', Char
'\x27e7'),
(Char
'\x27e8', Char
'\x27e9'),
(Char
'\x27ea', Char
'\x27eb'),
(Char
'\x27ec', Char
'\x27ed'),
(Char
'\x27ee', Char
'\x27ef'),
(Char
'\x2983', Char
'\x2984'),
(Char
'\x2985', Char
'\x2986'),
(Char
'\x2987', Char
'\x2988'),
(Char
'\x2989', Char
'\x298a'),
(Char
'\x298b', Char
'\x298c'),
(Char
'\x298d', Char
'\x2990'),
(Char
'\x298f', Char
'\x298e'),
(Char
'\x2991', Char
'\x2992'),
(Char
'\x2993', Char
'\x2994'),
(Char
'\x2995', Char
'\x2996'),
(Char
'\x2997', Char
'\x2998'),
(Char
'\x29d8', Char
'\x29d9'),
(Char
'\x29da', Char
'\x29db'),
(Char
'\x29fc', Char
'\x29fd'),
(Char
'\x2e22', Char
'\x2e23'),
(Char
'\x2e24', Char
'\x2e25'),
(Char
'\x2e26', Char
'\x2e27'),
(Char
'\x2e28', Char
'\x2e29'),
(Char
'\x3008', Char
'\x3009'),
(Char
'\x300a', Char
'\x300b'),
(Char
'\x300c', Char
'\x300d'),
(Char
'\x300e', Char
'\x300f'),
(Char
'\x3010', Char
'\x3011'),
(Char
'\x3014', Char
'\x3015'),
(Char
'\x3016', Char
'\x3017'),
(Char
'\x3018', Char
'\x3019'),
(Char
'\x301a', Char
'\x301b'),
(Char
'\xfe59', Char
'\xfe5a'),
(Char
'\xfe5b', Char
'\xfe5c'),
(Char
'\xfe5d', Char
'\xfe5e'),
(Char
'\xff08', Char
'\xff09'),
(Char
'\xff3b', Char
'\xff3d'),
(Char
'\xff5b', Char
'\xff5d'),
(Char
'\xff5f', Char
'\xff60'),
(Char
'\xff62', Char
'\xff63')
]
brackets ::
[Char]
brackets :: String
brackets = [Char
ci | ~(Char
ca, Char
cb) <- [(Char, Char)]
bracketMaps, Char
ci <- [Char
ca, Char
cb]]
openBrackets ::
[Char]
openBrackets :: String
openBrackets = ((Char, Char) -> Char) -> [(Char, Char)] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Char, Char) -> Char
forall a b. (a, b) -> a
fst [(Char, Char)]
bracketMaps
closeBrackets ::
[Char]
closeBrackets :: String
closeBrackets = ((Char, Char) -> Char) -> [(Char, Char)] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Char, Char) -> Char
forall a b. (a, b) -> b
snd [(Char, Char)]
bracketMaps
toClose :: Map Char Char
toClose :: Map Char Char
toClose = [(Char, Char)] -> Map Char Char
forall k a. Ord k => [(k, a)] -> Map k a
fromList [(Char, Char)]
bracketMaps
toOpen :: Map Char Char
toOpen :: Map Char Char
toOpen = [(Char, Char)] -> Map Char Char
forall k a. Ord k => [(k, a)] -> Map k a
fromList (((Char, Char) -> (Char, Char)) -> [(Char, Char)] -> [(Char, Char)]
forall a b. (a -> b) -> [a] -> [b]
map (Char, Char) -> (Char, Char)
forall a b. (a, b) -> (b, a)
swap [(Char, Char)]
bracketMaps)
isBracket ::
Char ->
Bool
isBracket :: Char -> Bool
isBracket Char
c = Map Char Char -> Bool
forall {a}. Map Char a -> Bool
go Map Char Char
toClose Bool -> Bool -> Bool
|| Map Char Char -> Bool
forall {a}. Map Char a -> Bool
go Map Char Char
toOpen
where
go :: Map Char a -> Bool
go = Char -> Map Char a -> Bool
forall k a. Ord k => k -> Map k a -> Bool
member Char
c
isOpenBracket ::
Char ->
Bool
isOpenBracket :: Char -> Bool
isOpenBracket = (Char -> Map Char Char -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`member` Map Char Char
toClose)
isCloseBracket ::
Char ->
Bool
isCloseBracket :: Char -> Bool
isCloseBracket = (Char -> Map Char Char -> Bool
forall k a. Ord k => k -> Map k a -> Bool
`member` Map Char Char
toOpen)
bracketType :: Char -> Maybe BracketType
bracketType :: Char -> Maybe BracketType
bracketType Char
c
| Map Char Char -> Bool
forall {a}. Map Char a -> Bool
go Map Char Char
toClose = BracketType -> Maybe BracketType
forall a. a -> Maybe a
Just BracketType
Open
| Map Char Char -> Bool
forall {a}. Map Char a -> Bool
go Map Char Char
toOpen = BracketType -> Maybe BracketType
forall a. a -> Maybe a
Just BracketType
Close
| Bool
otherwise = Maybe BracketType
forall a. Maybe a
Nothing
where
go :: Map Char a -> Bool
go = Char -> Map Char a -> Bool
forall k a. Ord k => k -> Map k a -> Bool
member Char
c
bracketType' :: Char -> BracketType
bracketType' :: Char -> BracketType
bracketType' Char
c
| Char -> Map Char Char -> Bool
forall k a. Ord k => k -> Map k a -> Bool
member Char
c Map Char Char
toClose = BracketType
Open
| Bool
otherwise = BracketType
Close
getOppositeChar ::
Char ->
Maybe Char
getOppositeChar :: Char -> Maybe Char
getOppositeChar Char
c = Map Char Char -> Maybe Char
forall {a}. Map Char a -> Maybe a
go Map Char Char
toClose Maybe Char -> Maybe Char -> Maybe Char
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Map Char Char -> Maybe Char
forall {a}. Map Char a -> Maybe a
go Map Char Char
toOpen
where
go :: Map Char a -> Maybe a
go = Char -> Map Char a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
lookup Char
c
getOppositeChar' ::
Char ->
Char
getOppositeChar' :: Char -> Char
getOppositeChar' = Char -> Maybe Char -> Char
forall a. a -> Maybe a -> a
fromMaybe (Char -> Maybe Char -> Char)
-> (Char -> Maybe Char) -> Char -> Char
forall a b. (Char -> a -> b) -> (Char -> a) -> Char -> b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Char -> Maybe Char
getOppositeChar