{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Djot.Attributes
( pAttributes
, parseAttributes
, AttrParserState
, AttrParseResult(..)
)
where
import Data.Char (isAlphaNum, isSpace, isPunctuation)
import Djot.AST (Attr(..))
import Djot.Parse
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as B8
import Data.ByteString.Char8 ( (!?) )
import Data.Typeable (Typeable)
import Data.Maybe (fromMaybe)
pAttributes :: Parser s Attr
pAttributes :: forall s. Parser s Attr
pAttributes = Parser s () -> Parser s ()
forall s a. Parser s a -> Parser s a
lookahead (Char -> Parser s ()
forall s. Char -> Parser s ()
asciiChar Char
'{') Parser s () -> Parser s ByteString -> Parser s ByteString
forall a b. Parser s a -> Parser s b -> Parser s b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser s ByteString
forall {s}. Parser s ByteString
getSlice Parser s ByteString
-> (ByteString -> Parser s Attr) -> Parser s Attr
forall a b. Parser s a -> (a -> Parser s b) -> Parser s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe AttrParserState -> ByteString -> Parser s Attr
forall {s}. Maybe AttrParserState -> ByteString -> Parser s Attr
go Maybe AttrParserState
forall a. Maybe a
Nothing
where
getSlice :: Parser s ByteString
getSlice = Parser s () -> Parser s ByteString
forall s a. Parser s a -> Parser s ByteString
byteStringOf (Parser s () -> Parser s ByteString)
-> Parser s () -> Parser s ByteString
forall a b. (a -> b) -> a -> b
$
Parser s () -> Parser s () -> Parser s () -> Parser s ()
forall s b a. Parser s b -> Parser s a -> Parser s a -> Parser s a
branch
(Parser s () -> Parser s ()
forall s a. Parser s a -> Parser s ()
skipSome ((Char -> Bool) -> Parser s ()
forall s. (Char -> Bool) -> Parser s ()
skipSatisfyByte (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'}')))
(Parser s () -> Parser s ()
forall s a. Parser s a -> Parser s ()
optional_ (Char -> Parser s ()
forall s. Char -> Parser s ()
asciiChar Char
'}'))
(Char -> Parser s ()
forall s. Char -> Parser s ()
asciiChar Char
'}')
go :: Maybe AttrParserState -> ByteString -> Parser s Attr
go Maybe AttrParserState
mbst ByteString
bs = do
case Maybe AttrParserState -> ByteString -> AttrParseResult
parseAttributes Maybe AttrParserState
mbst ByteString
bs of
Done (Attr
attr, Int
_off) -> Attr -> Parser s Attr
forall a. a -> Parser s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Attr
attr
Partial AttrParserState
st -> Parser s ByteString
forall {s}. Parser s ByteString
getSlice Parser s ByteString
-> (ByteString -> Parser s Attr) -> Parser s Attr
forall a b. Parser s a -> (a -> Parser s b) -> Parser s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Maybe AttrParserState -> ByteString -> Parser s Attr
go (AttrParserState -> Maybe AttrParserState
forall a. a -> Maybe a
Just AttrParserState
st)
Failed Int
_off -> Parser s Attr
forall s a. Parser s a
failed
data AttrParseResult =
Done (Attr, Int)
| Failed Int
| Partial AttrParserState
deriving (Int -> AttrParseResult -> ShowS
[AttrParseResult] -> ShowS
AttrParseResult -> String
(Int -> AttrParseResult -> ShowS)
-> (AttrParseResult -> String)
-> ([AttrParseResult] -> ShowS)
-> Show AttrParseResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttrParseResult -> ShowS
showsPrec :: Int -> AttrParseResult -> ShowS
$cshow :: AttrParseResult -> String
show :: AttrParseResult -> String
$cshowList :: [AttrParseResult] -> ShowS
showList :: [AttrParseResult] -> ShowS
Show, Typeable)
data AttrParserState =
AttrParserState
{ AttrParserState -> AState
aState :: AState
, AttrParserState -> ByteString
subject :: ByteString
, AttrParserState -> Int
offset :: Int
, AttrParserState -> [AttrPart]
parts :: [AttrPart] }
deriving (Int -> AttrParserState -> ShowS
[AttrParserState] -> ShowS
AttrParserState -> String
(Int -> AttrParserState -> ShowS)
-> (AttrParserState -> String)
-> ([AttrParserState] -> ShowS)
-> Show AttrParserState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttrParserState -> ShowS
showsPrec :: Int -> AttrParserState -> ShowS
$cshow :: AttrParserState -> String
show :: AttrParserState -> String
$cshowList :: [AttrParserState] -> ShowS
showList :: [AttrParserState] -> ShowS
Show, Typeable)
data AState =
SCANNING
| AFTER_KEY
| SCANNING_VALUE
| SCANNING_QUOTED_VALUE
| SCANNING_ESCAPE
|
| FAIL
| DONE
| START
deriving (AState -> AState -> Bool
(AState -> AState -> Bool)
-> (AState -> AState -> Bool) -> Eq AState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AState -> AState -> Bool
== :: AState -> AState -> Bool
$c/= :: AState -> AState -> Bool
/= :: AState -> AState -> Bool
Eq, Eq AState
Eq AState =>
(AState -> AState -> Ordering)
-> (AState -> AState -> Bool)
-> (AState -> AState -> Bool)
-> (AState -> AState -> Bool)
-> (AState -> AState -> Bool)
-> (AState -> AState -> AState)
-> (AState -> AState -> AState)
-> Ord AState
AState -> AState -> Bool
AState -> AState -> Ordering
AState -> AState -> AState
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 :: AState -> AState -> Ordering
compare :: AState -> AState -> Ordering
$c< :: AState -> AState -> Bool
< :: AState -> AState -> Bool
$c<= :: AState -> AState -> Bool
<= :: AState -> AState -> Bool
$c> :: AState -> AState -> Bool
> :: AState -> AState -> Bool
$c>= :: AState -> AState -> Bool
>= :: AState -> AState -> Bool
$cmax :: AState -> AState -> AState
max :: AState -> AState -> AState
$cmin :: AState -> AState -> AState
min :: AState -> AState -> AState
Ord, Int -> AState -> ShowS
[AState] -> ShowS
AState -> String
(Int -> AState -> ShowS)
-> (AState -> String) -> ([AState] -> ShowS) -> Show AState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AState -> ShowS
showsPrec :: Int -> AState -> ShowS
$cshow :: AState -> String
show :: AState -> String
$cshowList :: [AState] -> ShowS
showList :: [AState] -> ShowS
Show, Typeable)
data AttrPart =
AttrId ByteString
| AttrClass ByteString
| AttrKey ByteString
| AttrValue ByteString
deriving (AttrPart -> AttrPart -> Bool
(AttrPart -> AttrPart -> Bool)
-> (AttrPart -> AttrPart -> Bool) -> Eq AttrPart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AttrPart -> AttrPart -> Bool
== :: AttrPart -> AttrPart -> Bool
$c/= :: AttrPart -> AttrPart -> Bool
/= :: AttrPart -> AttrPart -> Bool
Eq, Eq AttrPart
Eq AttrPart =>
(AttrPart -> AttrPart -> Ordering)
-> (AttrPart -> AttrPart -> Bool)
-> (AttrPart -> AttrPart -> Bool)
-> (AttrPart -> AttrPart -> Bool)
-> (AttrPart -> AttrPart -> Bool)
-> (AttrPart -> AttrPart -> AttrPart)
-> (AttrPart -> AttrPart -> AttrPart)
-> Ord AttrPart
AttrPart -> AttrPart -> Bool
AttrPart -> AttrPart -> Ordering
AttrPart -> AttrPart -> AttrPart
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 :: AttrPart -> AttrPart -> Ordering
compare :: AttrPart -> AttrPart -> Ordering
$c< :: AttrPart -> AttrPart -> Bool
< :: AttrPart -> AttrPart -> Bool
$c<= :: AttrPart -> AttrPart -> Bool
<= :: AttrPart -> AttrPart -> Bool
$c> :: AttrPart -> AttrPart -> Bool
> :: AttrPart -> AttrPart -> Bool
$c>= :: AttrPart -> AttrPart -> Bool
>= :: AttrPart -> AttrPart -> Bool
$cmax :: AttrPart -> AttrPart -> AttrPart
max :: AttrPart -> AttrPart -> AttrPart
$cmin :: AttrPart -> AttrPart -> AttrPart
min :: AttrPart -> AttrPart -> AttrPart
Ord, Int -> AttrPart -> ShowS
[AttrPart] -> ShowS
AttrPart -> String
(Int -> AttrPart -> ShowS)
-> (AttrPart -> String) -> ([AttrPart] -> ShowS) -> Show AttrPart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AttrPart -> ShowS
showsPrec :: Int -> AttrPart -> ShowS
$cshow :: AttrPart -> String
show :: AttrPart -> String
$cshowList :: [AttrPart] -> ShowS
showList :: [AttrPart] -> ShowS
Show, Typeable)
parseAttributes :: Maybe AttrParserState -> ByteString -> AttrParseResult
parseAttributes :: Maybe AttrParserState -> ByteString -> AttrParseResult
parseAttributes Maybe AttrParserState
mbState ByteString
bs =
case AttrParserState -> AttrParserState
go (AttrParserState -> Maybe AttrParserState -> AttrParserState
forall a. a -> Maybe a -> a
fromMaybe AttrParserState{ aState :: AState
aState = AState
START
, subject :: ByteString
subject = ByteString
bs
, offset :: Int
offset = Int
0
, parts :: [AttrPart]
parts = [] } Maybe AttrParserState
mbState) of
AttrParserState{ aState :: AttrParserState -> AState
aState = AState
DONE, parts :: AttrParserState -> [AttrPart]
parts = [AttrPart]
attparts, offset :: AttrParserState -> Int
offset = Int
off } ->
(Attr, Int) -> AttrParseResult
Done ([AttrPart] -> Attr
attrPartsToAttr [AttrPart]
attparts, Int
off)
AttrParserState{ aState :: AttrParserState -> AState
aState = AState
FAIL, offset :: AttrParserState -> Int
offset = Int
off } -> Int -> AttrParseResult
Failed Int
off
AttrParserState
st -> AttrParserState -> AttrParseResult
Partial AttrParserState
st
where
go :: AttrParserState -> AttrParserState
go :: AttrParserState -> AttrParserState
go st :: AttrParserState
st@(AttrParserState AState
_ ByteString
subj Int
off [AttrPart]
_) =
case ByteString
subj ByteString -> Int -> Maybe Char
!? Int
off of
Maybe Char
Nothing -> AttrParserState
st
Just Char
nextc ->
case AttrParserState -> AState
aState AttrParserState
st of
AState
SCANNING ->
case Char
nextc of
Char
'}' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = DONE, offset = off + 1 }
Char
'%' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING_COMMENT, offset = off + 1 }
Char
'#' -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart Char -> Bool
isNameChar ByteString -> AttrPart
AttrId AState
SCANNING AttrParserState
st{ offset = off + 1 }
Char
'.' -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart Char -> Bool
isNameChar ByteString -> AttrPart
AttrClass AState
SCANNING AttrParserState
st{ offset = off + 1 }
Char
c | Char -> Bool
isKeyChar Char
c -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart Char -> Bool
isKeyChar ByteString -> AttrPart
AttrKey AState
AFTER_KEY AttrParserState
st
Char
c | Char -> Bool
isWs Char
c -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> AttrParserState -> AttrParserState
skipWhile Char -> Bool
isWs AttrParserState
st
Char
_ -> AttrParserState
st{ aState = FAIL }
AState
AFTER_KEY ->
case Char
nextc of
Char
'=' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING_VALUE, offset = off + 1 }
Char
_ -> AttrParserState
st{ aState = FAIL }
AState
SCANNING_VALUE ->
case Char
nextc of
Char
'"' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING_QUOTED_VALUE, offset = off + 1 }
Char
c | Char -> Bool
isBareValChar Char
c -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart Char -> Bool
isBareValChar ByteString -> AttrPart
AttrValue AState
SCANNING AttrParserState
st
Char
_ -> AttrParserState
st{ aState = FAIL }
AState
SCANNING_QUOTED_VALUE ->
case Char
nextc of
Char
'"' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING, offset = off + 1 }
Char
'\\' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING_ESCAPE, offset = off + 1 }
Char
c | Char -> Bool
isWs Char
c ->
let st' :: AttrParserState
st' = (Char -> Bool) -> AttrParserState -> AttrParserState
skipWhile Char -> Bool
isWs AttrParserState
st
in AttrParserState -> AttrParserState
go AttrParserState
st'{ parts = AttrValue " " : parts st' }
Char
_ -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart (\Char
c -> Bool -> Bool
not (Char -> Bool
isWs Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'"' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\\'))
ByteString -> AttrPart
AttrValue AState
SCANNING_QUOTED_VALUE AttrParserState
st
AState
SCANNING_ESCAPE ->
AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING_QUOTED_VALUE, offset = off + 1,
parts = AttrValue (B8.singleton nextc) : parts st }
AState
SCANNING_COMMENT ->
case Char
nextc of
Char
'%' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING, offset = off + 1 }
Char
'}' -> AttrParserState
st{ aState = DONE, offset = off + 1 }
Char
_ -> AttrParserState -> AttrParserState
go (AttrParserState -> AttrParserState)
-> AttrParserState -> AttrParserState
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> AttrParserState -> AttrParserState
skipWhile (\Char
c -> Bool -> Bool
not (Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'%' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'}')) AttrParserState
st
AState
FAIL -> AttrParserState
st
AState
DONE -> AttrParserState
st
AState
START ->
case Char
nextc of
Char
'{' -> AttrParserState -> AttrParserState
go AttrParserState
st{ aState = SCANNING, offset = off + 1 }
Char
_ -> AttrParserState
st{ aState = FAIL }
takePart :: (Char -> Bool) -> (ByteString -> AttrPart) -> AState ->
AttrParserState -> AttrParserState
takePart :: (Char -> Bool)
-> (ByteString -> AttrPart)
-> AState
-> AttrParserState
-> AttrParserState
takePart Char -> Bool
charP ByteString -> AttrPart
partConstructor AState
nextstate AttrParserState
st =
case AttrParserState -> ByteString
subject AttrParserState
st ByteString -> Int -> Maybe Char
!? AttrParserState -> Int
offset AttrParserState
st of
Just Char
c | Char -> Bool
charP Char
c ->
let val :: ByteString
val = (Char -> Bool) -> ByteString -> ByteString
B8.takeWhile Char -> Bool
charP (Int -> ByteString -> ByteString
B8.drop (AttrParserState -> Int
offset AttrParserState
st) (AttrParserState -> ByteString
subject AttrParserState
st))
in AttrParserState
st{ aState = nextstate,
offset = offset st + B8.length val,
parts = partConstructor val : parts st }
Maybe Char
_ -> AttrParserState
st{ aState = FAIL }
skipWhile :: (Char -> Bool) -> AttrParserState -> AttrParserState
skipWhile :: (Char -> Bool) -> AttrParserState -> AttrParserState
skipWhile Char -> Bool
charP AttrParserState
st =
case (Char -> Bool) -> ByteString -> Maybe Int
B8.findIndex (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
charP) (Int -> ByteString -> ByteString
B8.drop (AttrParserState -> Int
offset AttrParserState
st) (AttrParserState -> ByteString
subject AttrParserState
st)) of
Maybe Int
Nothing -> AttrParserState
st{ offset = B8.length (subject st) }
Just Int
i -> AttrParserState
st{ offset = offset st + i }
attrPartsToAttr :: [AttrPart] -> Attr
attrPartsToAttr :: [AttrPart] -> Attr
attrPartsToAttr = [AttrPart] -> Attr
go
where
go :: [AttrPart] -> Attr
go [] = [(ByteString, ByteString)] -> Attr
Attr []
go (AttrId ByteString
bs : [AttrPart]
xs) = (Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> [(ByteString, ByteString)] -> Attr
Attr [(ByteString
"id",ByteString
bs)]) (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ [AttrPart] -> Attr
go [AttrPart]
xs
go (AttrClass ByteString
bs : [AttrPart]
xs) = (Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> [(ByteString, ByteString)] -> Attr
Attr [(ByteString
"class",ByteString
bs)]) (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ [AttrPart] -> Attr
go [AttrPart]
xs
go [AttrPart]
zs =
case (AttrPart -> Bool) -> [AttrPart] -> ([AttrPart], [AttrPart])
forall a. (a -> Bool) -> [a] -> ([a], [a])
break AttrPart -> Bool
isAttrKey [AttrPart]
zs of
([AttrPart]
vs, AttrKey ByteString
bs : [AttrPart]
xs) ->
(Attr -> Attr -> Attr
forall a. Semigroup a => a -> a -> a
<> [(ByteString, ByteString)] -> Attr
Attr [(ByteString
bs, [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat ([ByteString] -> [ByteString]
forall a. [a] -> [a]
reverse ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ (AttrPart -> ByteString) -> [AttrPart] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map AttrPart -> ByteString
getAttrVal [AttrPart]
vs))]) (Attr -> Attr) -> Attr -> Attr
forall a b. (a -> b) -> a -> b
$ [AttrPart] -> Attr
go [AttrPart]
xs
([AttrPart], [AttrPart])
_ -> [(ByteString, ByteString)] -> Attr
Attr []
isAttrKey :: AttrPart -> Bool
isAttrKey (AttrKey ByteString
_) = Bool
True
isAttrKey AttrPart
_ = Bool
False
getAttrVal :: AttrPart -> ByteString
getAttrVal (AttrValue ByteString
bs) = ByteString
bs
getAttrVal AttrPart
_ = ByteString
forall a. Monoid a => a
mempty
isNameChar :: Char -> Bool
isNameChar :: Char -> Bool
isNameChar Char
c = Bool -> Bool
not (Char -> Bool
isSpace Char
c)
Bool -> Bool -> Bool
&& (Bool -> Bool
not (Char -> Bool
isPunctuation Char
c) Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
isKeyChar :: Char -> Bool
isKeyChar :: Char -> Bool
isKeyChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'
isBareValChar :: Char -> Bool
isBareValChar :: Char -> Bool
isBareValChar Char
c = Char -> Bool
isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-'