File: Arsec.hs

package info (click to toggle)
ghc 9.10.3-1
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 168,924 kB
  • sloc: haskell: 713,548; ansic: 84,223; cpp: 30,255; javascript: 9,003; sh: 7,870; fortran: 3,527; python: 3,228; asm: 2,523; makefile: 2,326; yacc: 1,570; lisp: 532; xml: 196; perl: 111; csh: 2
file content (49 lines) | stat: -rw-r--r-- 1,320 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
module Arsec
    (
      Comment
    , comment
    , semi
    , showC
    , unichar
    , unichars
    , module Control.Applicative
    , module Control.Monad
    , module Data.Char
    , module Text.ParserCombinators.Parsec.Char
    , module Text.ParserCombinators.Parsec.Combinator
    , module Text.ParserCombinators.Parsec.Error
    , module Text.ParserCombinators.Parsec.Prim
    ) where

import Prelude hiding (head, tail)
import Control.Monad
import Control.Applicative
import Data.Char
import Numeric (readHex, showHex)
import Text.ParserCombinators.Parsec.Char hiding (lower, upper)
import Text.ParserCombinators.Parsec.Combinator hiding (optional)
import Text.ParserCombinators.Parsec.Error
import Text.ParserCombinators.Parsec.Prim hiding ((<|>), many)

type Comment = String

unichar :: Parser Char
unichar = do
  digits <- many1 hexDigit
  case readHex digits of
    [] -> error "unichar: cannot parse hex digits"
    (hd, _) : _ -> pure $ chr hd

unichars :: Parser [Char]
unichars = manyTill (unichar <* spaces) semi

semi :: Parser ()
semi = char ';' *> spaces *> pure ()

comment :: Parser Comment
comment = (char '#' *> manyTill anyToken (char '\n')) <|> string "\n"

showC :: Char -> String
showC c = "'\\x" ++ d ++ "'"
    where h = showHex (ord c) ""
          d = replicate (4 - length h) '0' ++ h