module Waargonaut.Types.JChar.Unescaped
(
Unescaped (..)
, AsUnescaped (..)
, parseUnescaped
) where
import Prelude (Eq, Ord (..), Show, (&&), (==), (||))
import Control.Category (id)
import Control.Lens (Prism', has, prism')
import Data.Foldable (any)
import Data.Function (($))
import Data.Functor ((<$>))
import Data.Char (Char, ord)
import Data.Maybe (Maybe (..))
import Text.Parser.Char (CharParsing, satisfy)
newtype Unescaped =
Unescaped Char
deriving (Eq, Ord, Show)
class AsUnescaped a where
_Unescaped :: Prism' a Unescaped
instance AsUnescaped Unescaped where
_Unescaped = id
instance AsUnescaped Char where
_Unescaped = prism'
(\(Unescaped c) -> c)
(\c -> if any ($ c) excluded then Nothing
else Just (Unescaped c)
)
where
excluded =
[ (== '\NUL')
, (== '"')
, (== '\\')
, \x ->
let
c = ord x
in
(c < 0x20 && c > 0x21) ||
(c < 0x23 && c > 0x5B) ||
(c < 0x5D && c > 0x10FFFF)
]
parseUnescaped ::
CharParsing f =>
f Unescaped
parseUnescaped =
Unescaped <$> satisfy (has _Unescaped)