{-# LANGUAGE OverloadedStrings #-}

module PDF.CFF (encoding) where

import Numeric (readInt)
import Data.Char (chr, intToDigit)
import Data.List (isPrefixOf)

import Data.Word
import Data.Bits

import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import qualified Data.ByteString.Lazy as BSL

import Data.Attoparsec.ByteString (Parser, parseOnly, word8, string)
import qualified Data.Attoparsec.ByteString as AP
import Data.Attoparsec.Combinator

import Control.Applicative

import Debug.Trace

import PDF.Definition

type SID = Integer

test :: FilePath -> IO Encoding
test FilePath
f = do
  ByteString
c <- FilePath -> IO ByteString
BS.readFile FilePath
f
  Encoding -> IO Encoding
forall (m :: * -> *) a. Monad m => a -> m a
return (Encoding -> IO Encoding) -> Encoding -> IO Encoding
forall a b. (a -> b) -> a -> b
$ ByteString -> Encoding
encoding ByteString
c

encoding :: ByteString -> Encoding
encoding :: ByteString -> Encoding
encoding ByteString
c =
  [(Char, FilePath)] -> Encoding
Encoding ([(Char, FilePath)] -> Encoding) -> [(Char, FilePath)] -> Encoding
forall a b. (a -> b) -> a -> b
$ ((SID, Char) -> (Char, FilePath))
-> [(SID, Char)] -> [(Char, FilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (SID, Char) -> (Char, FilePath)
findEncodings ([(SID, Char)] -> [(Char, FilePath)])
-> [(SID, Char)] -> [(Char, FilePath)]
forall a b. (a -> b) -> a -> b
$ [SID] -> FilePath -> [(SID, Char)]
forall a b. [a] -> [b] -> [(a, b)]
zip [SID]
charset FilePath
encodings

  where
    ds :: [ByteString]
ds = ByteString -> [ByteString]
parseTopDictInd ByteString
c
    encodings :: FilePath
encodings  = (ByteString -> FilePath) -> [ByteString] -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ByteString -> ByteString -> FilePath
parseEncoding ByteString
c) [ByteString]
ds
    charset :: [SID]
charset = (ByteString -> [SID]) -> [ByteString] -> [SID]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (ByteString -> ByteString -> [SID]
parseCharset ByteString
c) [ByteString]
ds
    fontname :: FilePath
fontname = [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([FilePath] -> FilePath) -> [FilePath] -> FilePath
forall a b. (a -> b) -> a -> b
$ (ByteString -> FilePath) -> [ByteString] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (ByteString -> ByteString -> FilePath
parseFontname ByteString
c) [ByteString]
ds
    strings :: [FilePath]
strings = case Parser [FilePath] -> ByteString -> Either FilePath [FilePath]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly Parser [FilePath]
stringInd ByteString
c of
                Right [FilePath]
arr -> [FilePath]
arr
                Left FilePath
e -> FilePath -> [FilePath]
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse STRING Index"

    findEncodings :: (SID, Char) -> (Char, String)
    findEncodings :: (SID, Char) -> (Char, FilePath)
findEncodings (SID
char,Char
enc) =
      case SID
char of
        SID
s | SID
s SID -> SID -> Bool
forall a. Ord a => a -> a -> Bool
> SID
390 -> (Char
enc, FilePath -> FilePath
forall p. (Eq p, IsString p, Semigroup p) => p -> p
stringToText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ [FilePath]
strings [FilePath] -> Int -> FilePath
forall a. [a] -> Int -> a
!! SID -> Int
forall a. Num a => SID -> a
fromInteger (SID
char SID -> SID -> SID
forall a. Num a => a -> a -> a
- SID
390 SID -> SID -> SID
forall a. Num a => a -> a -> a
- SID
1))
          | SID
s SID -> SID -> Bool
forall a. Ord a => a -> a -> Bool
> SID
95 -> (Char
enc, SID -> FilePath
sidToText SID
s)
          | Bool
otherwise -> (Char
enc, [Char
enc])

    -- defined in String INDEX of each font
    stringToText :: p -> p
stringToText p
"a113" = p
"‡"
    stringToText p
"a114" = p
"・"
    stringToText p
"trianglesolid" = p
"▲"
    stringToText p
x = p
"[CFF:String " p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
x p -> p -> p
forall a. Semigroup a => a -> a -> a
<> p
"]"

    -- pre-defined in Appendix C of CFF specs
    sidToText :: SID -> FilePath
sidToText SID
n = [SID -> [(SID, Char)] -> FilePath
forall a. (Eq a, Num a) => a -> [(a, Char)] -> FilePath
complementSID SID
0 [(SID, Char)]
predefinedChars FilePath -> Int -> Char
forall a. [a] -> Int -> a
!! SID -> Int
forall a. Num a => SID -> a
fromInteger SID
n]

parseTopDictInd :: ByteString -> [ByteString]
parseTopDictInd :: ByteString -> [ByteString]
parseTopDictInd ByteString
c = case Parser [ByteString] -> ByteString -> Either FilePath [ByteString]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly (Parser SID
header Parser SID -> Parser [ByteString] -> Parser [ByteString]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser [ByteString]
index Parser [ByteString] -> Parser [ByteString] -> Parser [ByteString]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser [ByteString]
index) ByteString
c of
  Right [ByteString]
ds -> [ByteString]
ds
  Left FilePath
e -> FilePath -> [ByteString]
forall a. HasCallStack => FilePath -> a
error FilePath
"Can not find Top DICT INDEX"

parseEncoding :: ByteString -> ByteString -> [Char]
parseEncoding :: ByteString -> ByteString -> FilePath
parseEncoding ByteString
c ByteString
d = case Parser [([Word8], [DictOp])]
-> ByteString -> Either FilePath [([Word8], [DictOp])]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly (Parser ByteString ([Word8], [DictOp])
-> Parser [([Word8], [DictOp])]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser ByteString ([Word8], [DictOp])
dict) ByteString
d of
  -- '16' is key for 'Encoding' in Top DICT
  Right [([Word8], [DictOp])]
dictData -> case [Word8] -> [([Word8], [DictOp])] -> Maybe [DictOp]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Word8
16] [([Word8], [DictOp])]
dictData of 
    Just (DictInt Int
0:[]) -> []  
    Just (DictInt Int
1:[]) -> [] -- Expert Encoding (not supported)
    Just (DictInt Int
n:[]) -> -- n is offset
      case Parser [SID] -> ByteString -> Either FilePath [SID]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly Parser [SID]
encodingArray (ByteString -> Either FilePath [SID])
-> ByteString -> Either FilePath [SID]
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
BS.drop Int
n ByteString
c of
        Right [SID]
arr -> (SID -> Char) -> [SID] -> FilePath
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr (Int -> Char) -> (SID -> Int) -> SID -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SID -> Int
forall a. Num a => SID -> a
fromInteger) [SID]
arr
        Left FilePath
e -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse Encoding Array"
    Just [DictOp]
a -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error ([DictOp] -> FilePath
forall a. Show a => a -> FilePath
show [DictOp]
a)
    Maybe [DictOp]
Nothing -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"No Encodind Array in " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [([Word8], [DictOp])] -> FilePath
forall a. Show a => a -> FilePath
show [([Word8], [DictOp])]
dictData
  Left FilePath
_ -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse Top DICT in CFF"

parseFontname :: ByteString -> ByteString -> FilePath
parseFontname ByteString
c ByteString
d = case Parser [([Word8], [DictOp])]
-> ByteString -> Either FilePath [([Word8], [DictOp])]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly (Parser ByteString ([Word8], [DictOp])
-> Parser [([Word8], [DictOp])]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser ByteString ([Word8], [DictOp])
dict) ByteString
d of
  Right [([Word8], [DictOp])]
dictData -> case [Word8] -> [([Word8], [DictOp])] -> Maybe [DictOp]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Word8
2] [([Word8], [DictOp])]
dictData of
    Just (DictInt Int
n:[]) ->
      case Parser [FilePath] -> ByteString -> Either FilePath [FilePath]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly Parser [FilePath]
stringInd ByteString
c of
        Right [FilePath]
arr -> [FilePath]
arr [FilePath] -> Int -> FilePath
forall a. [a] -> Int -> a
!! (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
390 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) -- 390 seems to be a magic number
        Left FilePath
e -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse Fontname"
    Just [DictOp]
a -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error ([DictOp] -> FilePath
forall a. Show a => a -> FilePath
show [DictOp]
a)
    Maybe [DictOp]
Nothing -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ FilePath
"No Fontname in " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> [([Word8], [DictOp])] -> FilePath
forall a. Show a => a -> FilePath
show [([Word8], [DictOp])]
dictData
  Left FilePath
_ -> FilePath -> FilePath
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse Top DICT in CFF"

parseCharset :: ByteString -> ByteString -> [SID]
parseCharset ByteString
c ByteString
d = case Parser [([Word8], [DictOp])]
-> ByteString -> Either FilePath [([Word8], [DictOp])]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly (Parser ByteString ([Word8], [DictOp])
-> Parser [([Word8], [DictOp])]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 Parser ByteString ([Word8], [DictOp])
dict) ByteString
d of
  Right [([Word8], [DictOp])]
dictData -> case [Word8] -> [([Word8], [DictOp])] -> Maybe [DictOp]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [Word8
15] [([Word8], [DictOp])]
dictData of
    Just (DictInt Int
offset:[]) -> 
      case Parser [SID] -> ByteString -> Either FilePath [SID]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly ([ByteString] -> Parser [SID]
charsetData ([ByteString] -> Parser [SID]) -> [ByteString] -> Parser [SID]
forall a b. (a -> b) -> a -> b
$ ByteString -> [([Word8], [DictOp])] -> [ByteString]
forall a.
(Eq a, Num a, Show a) =>
ByteString -> [([a], [DictOp])] -> [ByteString]
charStringsInd ByteString
c [([Word8], [DictOp])]
dictData) (ByteString -> Either FilePath [SID])
-> ByteString -> Either FilePath [SID]
forall a b. (a -> b) -> a -> b
$
           Int -> ByteString -> ByteString
BS.drop Int
offset ByteString
c of
        Right [SID]
arr -> [SID]
arr
        Left FilePath
_ -> FilePath -> [SID]
forall a. HasCallStack => FilePath -> a
error FilePath
""
    Just [DictOp]
a -> FilePath -> [SID]
forall a. HasCallStack => FilePath -> a
error ([DictOp] -> FilePath
forall a. Show a => a -> FilePath
show [DictOp]
a)
    Maybe [DictOp]
Nothing -> FilePath -> [SID]
forall a. HasCallStack => FilePath -> a
error (FilePath -> [SID]) -> FilePath -> [SID]
forall a b. (a -> b) -> a -> b
$ FilePath
"No Charset in " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> [([Word8], [DictOp])] -> FilePath
forall a. Show a => a -> FilePath
show [([Word8], [DictOp])]
dictData
  Left FilePath
_ -> FilePath -> [SID]
forall a. HasCallStack => FilePath -> a
error FilePath
"Failed to parse Top DICT in CFF"

charStringsInd :: ByteString -> [([a], [DictOp])] -> [ByteString]
charStringsInd ByteString
c [([a], [DictOp])]
dictData = 
  case [a] -> [([a], [DictOp])] -> Maybe [DictOp]
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [a
17] [([a], [DictOp])]
dictData of
    Just (DictInt Int
offset:[]) -> 
      case Parser [ByteString] -> ByteString -> Either FilePath [ByteString]
forall a. Parser a -> ByteString -> Either FilePath a
parseOnly Parser [ByteString]
index (Int -> ByteString -> ByteString
BS.drop Int
offset ByteString
c) of
        Right [] -> FilePath -> [ByteString]
forall a. HasCallStack => FilePath -> a
error FilePath
"failed to get CharStrings"
        Right [ByteString]
ind -> [ByteString]
ind
        Left FilePath
"" -> FilePath -> [ByteString]
forall a. HasCallStack => FilePath -> a
error FilePath
"failed to get CharStrings"
    Maybe [DictOp]
Nothing -> FilePath -> [ByteString]
forall a. HasCallStack => FilePath -> a
error (FilePath -> [ByteString]) -> FilePath -> [ByteString]
forall a b. (a -> b) -> a -> b
$ FilePath
"No CharStrings in " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> [([a], [DictOp])] -> FilePath
forall a. Show a => a -> FilePath
show [([a], [DictOp])]
dictData

nameInd :: Parser [FilePath]
nameInd = (ByteString -> FilePath) -> [ByteString] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> FilePath
BSC.unpack ([ByteString] -> [FilePath])
-> Parser [ByteString] -> Parser [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser SID
header Parser SID -> Parser [ByteString] -> Parser [ByteString]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser [ByteString]
index)

dictInd :: Parser ByteString ByteString
dictInd = [ByteString] -> ByteString
BSC.concat ([ByteString] -> ByteString)
-> Parser [ByteString] -> Parser ByteString ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser SID
header Parser SID -> Parser [ByteString] -> Parser [ByteString]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser [ByteString]
index Parser [ByteString] -> Parser [ByteString] -> Parser [ByteString]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser [ByteString]
index)

stringInd :: Parser [FilePath]
stringInd = (ByteString -> FilePath) -> [ByteString] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map ByteString -> FilePath
BSC.unpack ([ByteString] -> [FilePath])
-> Parser [ByteString] -> Parser [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser SID
header Parser SID -> Parser [ByteString] -> Parser [ByteString]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser [ByteString]
index Parser [ByteString] -> Parser [ByteString] -> Parser [ByteString]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Parser [ByteString]
index Parser [ByteString] -> Parser [ByteString] -> Parser [ByteString]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser [ByteString]
index)

charsetData :: [ByteString] -> Parser [Integer]
charsetData :: [ByteString] -> Parser [SID]
charsetData [ByteString]
ind = do
  SID
format <- Int -> Parser SID
getCard Int
1
  SID -> Parser [SID]
forall a. (Eq a, Num a) => a -> Parser [SID]
charsetObj SID
format
  
  where
    -- .notdef must be excluded, so minus one
    charsetObj :: a -> Parser [SID]
charsetObj a
0 = Int -> Parser SID -> Parser [SID]
forall (m :: * -> *) a. Monad m => Int -> m a -> m [a]
count ([ByteString] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ByteString]
ind Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Parser SID
getSID 


encodingArray :: Parser [Integer]
encodingArray :: Parser [SID]
encodingArray = do
  SID
format <- Int -> Parser SID
getCard Int
1
  Int
p <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
  SID -> Int -> Parser [SID]
encodeObj SID
format Int
p

  where
    encodeObj :: Integer -> Int -> Parser [Integer]
    encodeObj :: SID -> Int -> Parser [SID]
encodeObj SID
0 Int
p = Int -> Parser SID -> Parser [SID]
forall (m :: * -> *) a. Monad m => Int -> m a -> m [a]
count (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) (Int -> Parser SID
getCard Int
1)
    encodeObj SID
1 Int
p = [[SID]] -> [SID]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[SID]] -> [SID]) -> Parser ByteString [[SID]] -> Parser [SID]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser [SID] -> Parser ByteString [[SID]]
forall (m :: * -> *) a. Monad m => Int -> m a -> m [a]
count Int
p Parser [SID]
getRange1
    encodeObj SID
_ Int
p = FilePath -> Parser [SID]
forall a. HasCallStack => FilePath -> a
error FilePath
"CFF Supplement Format is not supported."

    getRange1 :: Parser [Integer]
    getRange1 :: Parser [SID]
getRange1 = do
      SID
first <- Int -> Parser SID
getCard Int
1
      SID
nleft <- Int -> Parser SID
getCard Int
1
      [SID] -> Parser [SID]
forall (m :: * -> *) a. Monad m => a -> m a
return ([SID] -> Parser [SID]) -> [SID] -> Parser [SID]
forall a b. (a -> b) -> a -> b
$ [SID
first .. SID
first SID -> SID -> SID
forall a. Num a => a -> a -> a
+ SID
nleft]

data DictOp = DictInt Int | DictReal Double
  deriving (Int -> DictOp -> FilePath -> FilePath
[DictOp] -> FilePath -> FilePath
DictOp -> FilePath
(Int -> DictOp -> FilePath -> FilePath)
-> (DictOp -> FilePath)
-> ([DictOp] -> FilePath -> FilePath)
-> Show DictOp
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [DictOp] -> FilePath -> FilePath
$cshowList :: [DictOp] -> FilePath -> FilePath
show :: DictOp -> FilePath
$cshow :: DictOp -> FilePath
showsPrec :: Int -> DictOp -> FilePath -> FilePath
$cshowsPrec :: Int -> DictOp -> FilePath -> FilePath
Show)

dict :: Parser ByteString ([Word8], [DictOp])
dict = (([Word8] -> [DictOp] -> ([Word8], [DictOp]))
-> [DictOp] -> [Word8] -> ([Word8], [DictOp])
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,)) ([DictOp] -> [Word8] -> ([Word8], [DictOp]))
-> Parser ByteString [DictOp]
-> Parser ByteString ([Word8] -> ([Word8], [DictOp]))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser ByteString DictOp
-> Parser ByteString [Word8] -> Parser ByteString [DictOp]
forall (f :: * -> *) a b. Alternative f => f a -> f b -> f [a]
manyTill Parser ByteString DictOp
dictOp (Parser ByteString [Word8] -> Parser ByteString [Word8]
forall i a. Parser i a -> Parser i a
try (Parser ByteString [Word8] -> Parser ByteString [Word8])
-> Parser ByteString [Word8] -> Parser ByteString [Word8]
forall a b. (a -> b) -> a -> b
$ Parser ByteString [Word8] -> Parser ByteString [Word8]
forall i a. Parser i a -> Parser i a
lookAhead Parser ByteString [Word8]
dictKey)) Parser ByteString ([Word8] -> ([Word8], [DictOp]))
-> Parser ByteString [Word8]
-> Parser ByteString ([Word8], [DictOp])
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser ByteString [Word8]
dictKey

dictOp :: Parser DictOp
dictOp :: Parser ByteString DictOp
dictOp = do
  Int
b0 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
  Int -> Parser ByteString DictOp
opEnc Int
b0
  
  where
    opEnc :: Int -> Parser DictOp
    opEnc :: Int -> Parser ByteString DictOp
opEnc Int
b0 | Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
32 Bool -> Bool -> Bool
&& Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
246 = DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Int -> DictOp
DictInt (Int -> DictOp) -> Int -> DictOp
forall a b. (a -> b) -> a -> b
$ Int
b0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
139
             | Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
247 Bool -> Bool -> Bool
&& Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
250 = do
                 Int
b1 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Int -> DictOp
DictInt (Int -> DictOp) -> Int -> DictOp
forall a b. (a -> b) -> a -> b
$ (Int
b0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
247) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
256 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
b1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
108
             | Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
251 Bool -> Bool -> Bool
&& Int
b0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
254 = do
                 Int
b1 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Int -> DictOp
DictInt (Int -> DictOp) -> Int -> DictOp
forall a b. (a -> b) -> a -> b
$ - (Int
b0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
251) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
256 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
b1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
108
             | Int
b0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
28 = do
                 Int
b1 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 Int
b2 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Int -> DictOp
DictInt (Int -> DictOp) -> Int -> DictOp
forall a b. (a -> b) -> a -> b
$ Int
b1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
b2
             | Int
b0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
29 = do
                 Int
b1 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 Int
b2 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 Int
b3 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 Int
b4 <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
                 DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Int -> DictOp
DictInt (Int -> DictOp) -> Int -> DictOp
forall a b. (a -> b) -> a -> b
$  Int
b1 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
24 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
b2 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
16 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
b3 Int -> Int -> Int
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 Int -> Int -> Int
forall a. Bits a => a -> a -> a
.|. Int
b4
             | Int
b0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
30 = do
                 [Word8]
r <- Parser ByteString Word8 -> Parser ByteString [Word8]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 (Parser ByteString Word8 -> Parser ByteString [Word8])
-> Parser ByteString Word8 -> Parser ByteString [Word8]
forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> Parser ByteString Word8
AP.satisfy (\Word8
w -> (Word8
240 Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
.|. Word8
w) Word8 -> Word8 -> Word8
forall a. Bits a => a -> a -> a
`xor` Word8
255 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
0)
                 SID
f <- Int -> Parser SID
getCard Int
1
                 DictOp -> Parser ByteString DictOp
forall (m :: * -> *) a. Monad m => a -> m a
return (DictOp -> Parser ByteString DictOp)
-> DictOp -> Parser ByteString DictOp
forall a b. (a -> b) -> a -> b
$ Double -> DictOp
DictReal (Double -> DictOp) -> Double -> DictOp
forall a b. (a -> b) -> a -> b
$ [Word8] -> SID -> Double
forall p p p. Num p => p -> p -> p
readNibble [Word8]
r SID
f
             | Bool
otherwise = FilePath -> Parser ByteString DictOp
forall a. HasCallStack => FilePath -> a
error (Int -> FilePath
forall a. Show a => a -> FilePath
show Int
b0)
    readNibble :: p -> p -> p
readNibble p
s1 p
s2 = p
0

dictKey :: Parser [Word8]
dictKey :: Parser ByteString [Word8]
dictKey = do
  [Word8]
key <- [Parser ByteString [Word8]] -> Parser ByteString [Word8]
forall (f :: * -> *) a. Alternative f => [f a] -> f a
AP.choice [ Parser ByteString [Word8] -> Parser ByteString [Word8]
forall i a. Parser i a -> Parser i a
try (Parser ByteString [Word8] -> Parser ByteString [Word8])
-> Parser ByteString [Word8] -> Parser ByteString [Word8]
forall a b. (a -> b) -> a -> b
$ Parser ByteString Word8 -> Parser ByteString [Word8]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many1 (Parser ByteString Word8 -> Parser ByteString [Word8])
-> Parser ByteString Word8 -> Parser ByteString [Word8]
forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool) -> Parser ByteString Word8
AP.satisfy ((Word8 -> Bool) -> Parser ByteString Word8)
-> (Word8 -> Bool) -> Parser ByteString Word8
forall a b. (a -> b) -> a -> b
$ FilePath -> Word8 -> Bool
AP.inClass FilePath
"\0-\5\13-\18"
                   , Parser ByteString [Word8] -> Parser ByteString [Word8]
forall i a. Parser i a -> Parser i a
try (Parser ByteString [Word8] -> Parser ByteString [Word8])
-> Parser ByteString [Word8] -> Parser ByteString [Word8]
forall a b. (a -> b) -> a -> b
$ ((Word8 -> Word8 -> [Word8]) -> Word8 -> Word8 -> [Word8]
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Word8 -> [Word8] -> [Word8]) -> [Word8] -> Word8 -> [Word8]
forall a b c. (a -> b -> c) -> b -> a -> c
flip (:) ([Word8] -> Word8 -> [Word8])
-> (Word8 -> [Word8]) -> Word8 -> Word8 -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[])))
                     (Word8 -> Word8 -> [Word8])
-> Parser ByteString Word8 -> Parser ByteString (Word8 -> [Word8])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Bool) -> Parser ByteString Word8
AP.satisfy (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
12) Parser ByteString (Word8 -> [Word8])
-> Parser ByteString Word8 -> Parser ByteString [Word8]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Word8 -> Bool) -> Parser ByteString Word8
AP.satisfy ((Word8 -> Bool) -> Parser ByteString Word8)
-> (Word8 -> Bool) -> Parser ByteString Word8
forall a b. (a -> b) -> a -> b
$ FilePath -> Word8 -> Bool
AP.inClass FilePath
"\0-\8\20-\23\30-\38")
                   ]
  [Word8] -> Parser ByteString [Word8]
forall (m :: * -> *) a. Monad m => a -> m a
return [Word8]
key

index :: Parser [ByteString]
index :: Parser [ByteString]
index = do
  Int
indexCount <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
2
  Int
offSize <- SID -> Int
forall a. Num a => SID -> a
fromInteger (SID -> Int) -> Parser SID -> Parser ByteString Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID
getCard Int
1
  [Int]
offsets <- (SID -> Int) -> [SID] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map SID -> Int
forall a. Num a => SID -> a
fromInteger ([SID] -> [Int]) -> Parser [SID] -> Parser ByteString [Int]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser SID -> Parser [SID]
forall (m :: * -> *) a. Monad m => Int -> m a -> m [a]
count (Int
indexCountInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int -> Parser SID
getCard Int
offSize)
  [ByteString]
indexData <- [Int] -> Parser [ByteString]
repeatFor [Int]
offsets
  [ByteString] -> Parser [ByteString]
forall (m :: * -> *) a. Monad m => a -> m a
return [ByteString]
indexData
  where
    repeatFor :: [Int] -> Parser [ByteString]
repeatFor [Int]
ls = [Parser ByteString ByteString] -> Parser [ByteString]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence ([Parser ByteString ByteString] -> Parser [ByteString])
-> [Parser ByteString ByteString] -> Parser [ByteString]
forall a b. (a -> b) -> a -> b
$ (Int -> Parser ByteString ByteString)
-> [Int] -> [Parser ByteString ByteString]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Parser ByteString ByteString
AP.take ([Int] -> [Parser ByteString ByteString])
-> [Int] -> [Parser ByteString ByteString]
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
forall a. Num a => [a] -> [a]
differenciate [Int]
ls
    differenciate :: [a] -> [a]
differenciate [a]
ls = [a] -> [a]
forall a. [a] -> [a]
tail ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> [a] -> [a] -> [a]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> a -> a
forall a. Num a => a -> a -> a
subtract (a
0a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ls) [a]
ls

header :: Parser Integer
header :: Parser SID
header = do
  SID
major <- Int -> Parser SID
getCard Int
1
  SID
minor <- Int -> Parser SID
getCard Int
1
  SID
hrdSize <- Int -> Parser SID
getCard Int
1
  SID
offSize <- Int -> Parser SID
getCard Int
1
  SID -> Parser SID
forall (m :: * -> *) a. Monad m => a -> m a
return (SID -> Parser SID) -> SID -> Parser SID
forall a b. (a -> b) -> a -> b
$ SID
major

getCard :: Int -> Parser Integer
getCard :: Int -> Parser SID
getCard Int
n = ByteString -> SID
fromBytes (ByteString -> SID) -> Parser ByteString ByteString -> Parser SID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser ByteString ByteString
AP.take Int
n

getSID :: Parser SID
getSID :: Parser SID
getSID = ByteString -> SID
fromBytes (ByteString -> SID) -> Parser ByteString ByteString -> Parser SID
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Parser ByteString ByteString
AP.take Int
2

fromBytes :: ByteString -> Integer
fromBytes :: ByteString -> SID
fromBytes = (SID -> Word8 -> SID) -> SID -> ByteString -> SID
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
BS.foldl' SID -> Word8 -> SID
forall a a. (Bits a, Integral a, Num a) => a -> a -> a
f SID
0
  where
    f :: a -> a -> a
f a
a a
b = a
a a -> Int -> a
forall a. Bits a => a -> Int -> a
`shiftL` Int
8 a -> a -> a
forall a. Bits a => a -> a -> a
.|. a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
b

complementSID :: a -> [(a, Char)] -> FilePath
complementSID a
_ [] = []
complementSID a
i arr :: [(a, Char)]
arr@((a
n,Char
c):[(a, Char)]
rest) 
  | a
i a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
n = Char
cChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:(a -> [(a, Char)] -> FilePath
complementSID (a
ia -> a -> a
forall a. Num a => a -> a -> a
+a
1) [(a, Char)]
rest)
  | Bool
otherwise = Char
' 'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:(a -> [(a, Char)] -> FilePath
complementSID (a
ia -> a -> a
forall a. Num a => a -> a -> a
+a
1) [(a, Char)]
arr)

predefinedChars :: [(SID, Char)]
predefinedChars = 
  [ (SID
1, Char
' ')
  , (SID
2, Char
'!')
  , (SID
3, Char
'"')
  , (SID
4, Char
'#')
  , (SID
5, Char
'$')
  , (SID
6, Char
'%')
  , (SID
7, Char
'&')
  , (SID
8, Char
'’')
  , (SID
9, Char
'(')
  , (SID
10, Char
')')
  , (SID
11, Char
'*')
  , (SID
12, Char
'+')
  , (SID
13, Char
',')
  , (SID
14, Char
'-')
  , (SID
15, Char
'.')
  , (SID
16, Char
'/')
  , (SID
17, Char
'0')
  , (SID
18, Char
'1')
  , (SID
19, Char
'2')
  , (SID
20, Char
'3')
  , (SID
21, Char
'4')
  , (SID
22, Char
'5')
  , (SID
23, Char
'6')
  , (SID
24, Char
'7')
  , (SID
25, Char
'8')
  , (SID
26, Char
'9')
  , (SID
27, Char
':')
  , (SID
28, Char
';')
  , (SID
29, Char
'<')
  , (SID
30, Char
'=')
  , (SID
31, Char
'>')
  , (SID
32, Char
'?')
  , (SID
33, Char
'@')
  , (SID
34, Char
'A')
  , (SID
35, Char
'B')
  , (SID
36, Char
'C')
  , (SID
37, Char
'D')
  , (SID
38, Char
'E')
  , (SID
39, Char
'F')
  , (SID
40, Char
'G')
  , (SID
41, Char
'H')
  , (SID
42, Char
'I')
  , (SID
43, Char
'J')
  , (SID
44, Char
'K')
  , (SID
45, Char
'L')
  , (SID
46, Char
'M')
  , (SID
47, Char
'N')
  , (SID
48, Char
'O')
  , (SID
49, Char
'P')
  , (SID
50, Char
'Q')
  , (SID
51, Char
'R')
  , (SID
52, Char
'S')
  , (SID
53, Char
'T')
  , (SID
54, Char
'U')
  , (SID
55, Char
'V')
  , (SID
56, Char
'W')
  , (SID
57, Char
'X')
  , (SID
58, Char
'Y')
  , (SID
59, Char
'Z')
  , (SID
60, Char
'{')
  , (SID
61, Char
'/')
  , (SID
62, Char
'}')
  , (SID
63, Char
'^')
  , (SID
64, Char
'_')
  , (SID
65, Char
'‘')
  , (SID
66, Char
'a')
  , (SID
67, Char
'b')
  , (SID
68, Char
'c')
  , (SID
69, Char
'd')
  , (SID
70, Char
'e')
  , (SID
71, Char
'f')
  , (SID
72, Char
'g')
  , (SID
73, Char
'h')
  , (SID
74, Char
'i')
  , (SID
75, Char
'j')
  , (SID
76, Char
'k')
  , (SID
77, Char
'l')
  , (SID
78, Char
'm')
  , (SID
79, Char
'n')
  , (SID
80, Char
'o')
  , (SID
81, Char
'p')
  , (SID
82, Char
'q')
  , (SID
83, Char
'r')
  , (SID
84, Char
's')
  , (SID
85, Char
't')
  , (SID
86, Char
'u')
  , (SID
87, Char
'v')
  , (SID
88, Char
'w')
  , (SID
89, Char
'x')
  , (SID
90, Char
'y')
  , (SID
91, Char
'z')
  , (SID
92, Char
'[')
  , (SID
93, Char
'ˉ')
  , (SID
94, Char
']')
  , (SID
95, Char
'~')
  , (SID
96, Char
'¡')
  , (SID
97, Char
'¢')
  , (SID
98, Char
'£')
  , (SID
99, Char
'/')
  , (SID
100, Char
'¥')
  , (SID
101, Char
'ƒ')
  , (SID
102, Char
'§')
  , (SID
103, Char
'$')
  , (SID
104, Char
'\'')
  , (SID
105, Char
'“')
  , (SID
106, Char
'«')
  , (SID
107, Char
'‹')
  , (SID
108, Char
'›')
  , (SID
109, Char
'fi')
  , (SID
110, Char
'fl')
  , (SID
111, Char
'–')
  , (SID
112, Char
'†')
  , (SID
113, Char
'‡')
  , (SID
114, Char
'·')
  , (SID
115, Char
'❡')
  , (SID
116, Char
'・')
  , (SID
117, Char
'‚')
  , (SID
118, Char
'„')
  , (SID
119, Char
'”')
  , (SID
120, Char
'»')
  , (SID
121, Char
'…')
  , (SID
122, Char
'‰')
  , (SID
123, Char
'¿')
  , (SID
124, Char
'`')
  , (SID
125, Char
'´')
  , (SID
126, Char
'^')
  , (SID
127, Char
'~')
  , (SID
128, Char
'¯')
  , (SID
129, Char
'˘')
  , (SID
130, Char
'˙')
  , (SID
131, Char
'¨')
  , (SID
132, Char
'°')
  , (SID
133, Char
'¸')
  , (SID
134, Char
'˝')
  , (SID
135, Char
'˛')
  , (SID
136, Char
'ˇ')
  , (SID
137, Char
'—')
  , (SID
138, Char
'Æ')
  , (SID
139, Char
'ª')
  , (SID
140, Char
'Ł')
  , (SID
141, Char
'Ø')
  , (SID
142, Char
'Œ')
  , (SID
143, Char
'º')
  , (SID
144, Char
'æ')
  , (SID
145, Char
'ı')
  , (SID
146, Char
'ł')
  , (SID
147, Char
'ø')
  , (SID
148, Char
'œ')
  , (SID
149, Char
'ẞ')
  , (SID
150, Char
'¹')
  , (SID
151, Char
'¬')
  , (SID
152, Char
'µ')
  , (SID
153, Char
'™')
  , (SID
154, Char
'Ð')
  , (SID
155, Char
'½')
  , (SID
156, Char
'±')
  , (SID
157, Char
'Þ')
  , (SID
158, Char
'¼')
  , (SID
159, Char
'÷')
  , (SID
160, Char
'¦')
  , (SID
161, Char
'°')
  , (SID
162, Char
'þ')
  , (SID
163, Char
'¾')
  , (SID
164, Char
'²')
  , (SID
165, Char
'®')
  , (SID
166, Char
'-')
  , (SID
167, Char
'ð')
  , (SID
168, Char
'×')
  , (SID
169, Char
'³')
  , (SID
170, Char
'Ⓒ')
  , (SID
171, Char
'Á')
  , (SID
172, Char
'Â')
  , (SID
173, Char
'Ä')
  , (SID
174, Char
'À')
  , (SID
175, Char
'Å')
  , (SID
176, Char
'Ã')
  , (SID
177, Char
'Ç')
  , (SID
178, Char
'É')
  , (SID
179, Char
'Ê')
  , (SID
180, Char
'Ë')
  , (SID
181, Char
'È')
  , (SID
182, Char
'Í')
  , (SID
183, Char
'Î')
  , (SID
184, Char
'Ï')
  , (SID
185, Char
'Ì')
  , (SID
186, Char
'Ñ')
  , (SID
187, Char
'Ó')
  , (SID
188, Char
'Ô')
  , (SID
189, Char
'Ö')
  , (SID
190, Char
'Ò')
  , (SID
191, Char
'Õ')
  , (SID
192, Char
'Š')
  , (SID
193, Char
'Ú')
  , (SID
194, Char
'Û')
  , (SID
195, Char
'Ü')
  , (SID
196, Char
'Ù')
  , (SID
197, Char
'Ý')
  , (SID
198, Char
'Ÿ')
  , (SID
199, Char
'Ž')
  , (SID
200, Char
'á')
  , (SID
201, Char
'â')
  , (SID
202, Char
'ä')
  , (SID
203, Char
'à')
  , (SID
204, Char
'å')
  , (SID
205, Char
'ã')
  , (SID
206, Char
'ç')
  , (SID
207, Char
'é')
  , (SID
208, Char
'ê')
  , (SID
209, Char
'ë')
  , (SID
210, Char
'è')
  , (SID
211, Char
'í')
  , (SID
212, Char
'î')
  , (SID
213, Char
'ï')
  , (SID
214, Char
'ì')
  , (SID
215, Char
'ñ')
  , (SID
216, Char
'ó')
  , (SID
217, Char
'ô')
  , (SID
218, Char
'ö')
  , (SID
219, Char
'ò')
  , (SID
220, Char
'õ')
  , (SID
221, Char
'š')
  , (SID
222, Char
'ú')
  , (SID
223, Char
'û')
  , (SID
224, Char
'ü')
  , (SID
225, Char
'ù')
  , (SID
226, Char
'ý')
  , (SID
227, Char
'ÿ')
  , (SID
228, Char
'ž')
  ]