Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
type family FromChars1 (cs :: [Char]) (res :: Symbol) :: Symbol where ... Source #
FromChars1 '[] res = res | |
FromChars1 (c ': cs) res = FromChars1 cs (ConsSymbol c res) |
type family FromCharsReverse (cs :: [Char]) :: Symbol where ... Source #
FromCharsReverse cs = FromChars1 cs "" |
type family FromChars (cs :: [Char]) :: Symbol where ... Source #
FromChars cs = FromChars1 (Eval (Reverse cs)) "" |
type family ToChars (s :: Symbol) :: [Char] where ... Source #
ToChars s = ToChars1 (UnconsSymbol s) '[] |
type family AppendChar (s :: Symbol) (c :: Char) :: Symbol where ... Source #
AppendChar s c = AppendSymbol s (FromChar c) |
type family CharBetween1 (c1 :: Ordering) (c2 :: Ordering) :: Bool where ... Source #
CharBetween1 EQ LT = True | |
CharBetween1 LT EQ = True | |
CharBetween1 LT LT = True | |
CharBetween1 a b = False |
type family CharBetween (c :: Char) (lowerBound :: Char) (upperBound :: Char) :: Bool where ... Source #
CharBetween c lowerBound upperBound = CharBetween1 (CmpChar lowerBound c) (CmpChar c upperBound) |
type SpecialChars = '['.', '?', '>', '<', '+', '!', '%'] Source #
type family UnexpectedCharacterError (c :: Char) (expected :: Symbol) (prefix :: [Char]) (rest :: [Char]) :: k where ... Source #
UnexpectedCharacterError c expected prefix rest = TypeError (((((Text "Unexpected character: " :<>: Text (FromChar c)) :<>: Text "\n") :<>: (Text expected :<>: Text "\n")) :<>: ((Text "in " :<>: Text (FromCharsReverse prefix)) :<>: Text "\n")) :<>: (Text "in " :<>: Text (AppendSymbol (FromCharsReverse prefix) (FromChars rest)))) |
type family Parse1 (parsed :: [Char]) (rest :: [Char]) (tags :: [Tag]) :: [Tag] where ... Source #
Parse1 p '[] ts = ts | |
Parse1 p ('.' ': xs) ts = Parse1 ('.' ': p) xs (Tag'Dot ': ts) | |
Parse1 p ('?' ': xs) ts = Parse1 ('?' ': p) xs (Tag'QuestionMark ': ts) | |
Parse1 p ('>' ': xs) ts = Parse1 ('>' ': p) xs (Tag'RightArrow ': ts) | |
Parse1 p ('<' ': xs) ts = Parse1 ('<' ': p) xs (Tag'LeftArrow ': ts) | |
Parse1 p ('+' ': xs) ts = Parse1 ('+' ': p) xs (Tag'Plus ': ts) | |
Parse1 p ('!' ': xs) ts = Parse1 ('!' ': p) xs (Tag'ExclamationMark ': ts) | |
Parse1 p ('%' ': (x ': xs)) ts = If (CharBetween x '1' '9') (Parse1 (x ': ('%' ': p)) xs (Tag'PercentageNumber (DigitNat x) ': ts)) (If (IsSpecial x) (UnexpectedCharacterError x "Expected a letter or a digit\nafter '%'" p (x ': xs)) (Parse1 (x ': ('%' ': p)) xs (Tag'PercentageName (ConsSymbol x "") ': ts))) | |
Parse1 p (x ': xs) (Tag'PercentageName s ': ts) = Parse1 (x ': p) xs (Tag'PercentageName (AppendChar s x) ': ts) | |
Parse1 p (x ': xs) (Tag'PercentageNumber n ': ts) = If (CharBetween x '0' '9') (Parse1 (x ': p) xs (Tag'PercentageNumber ((n * 10) + DigitNat x) ': ts)) (UnexpectedCharacterError x "Expected a digit or a special character\nafter a digit" p (x ': xs)) | |
Parse1 p (x ': xs) (Tag'Name n ': ts) = Parse1 (x ': p) xs (Tag'Name (AppendChar n x) ': ts) | |
Parse1 p (x ': xs) ts = If (Eval (Or '[CharBetween x '0' '9'])) (UnexpectedCharacterError x "Expected a letter" p (x ': xs)) (Parse1 (x ': p) xs (Tag'Name (FromChar x) ': ts)) | |
Parse1 _ _ _ = TypeError (Text "cornercase!") |