module Web.Willow.Common.Encoding.EucJp
(
decoder
, decodeIndex0208
, encoder
, encodeIndex0208
) where
import qualified Control.Applicative as A
import qualified Data.ByteString.Short as BS.SH
import qualified Data.Char as C
import qualified Data.Maybe as Y
import qualified Data.Tuple as U
import qualified Data.Word as W
import Web.Willow.Common.Encoding.Common
import Web.Willow.Common.Parser
import Web.Willow.Common.Parser.Switch
decoder :: TextBuilder
decoder :: TextBuilder
decoder = StateT (Confidence, ()) (Parser ByteString) Word8
forall (m :: * -> *) stream token.
MonadParser m stream token =>
m token
next StateT (Confidence, ()) (Parser ByteString) Word8
-> (Word8 -> TextBuilder) -> TextBuilder
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)]
-> Word8 -> TextBuilder
forall (m :: * -> *) test out.
Alternative m =>
[SwitchCase test m out] -> test -> m out
switch
[ (Word8 -> Bool)
-> TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x8E) (TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String))
-> TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall a b. (a -> b) -> a -> b
$ do
Word8
second <- StateT (Confidence, ()) (Parser ByteString) Word8
forall (m :: * -> *) stream token.
MonadParser m stream token =>
m token
next
if Word8 -> Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> a -> Bool
range Word8
0xA1 Word8
0xDF Word8
second
then [Word8] -> Char -> TextBuilder
forall state. [Word8] -> Char -> StateTextBuilder state
emit [Word8
0x8E, Word8
second] (Char -> TextBuilder) -> (Int -> Char) -> Int -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Char
forall a. Enum a => Int -> a
toEnum (Int -> Char) -> (Int -> Int) -> Int -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
0xFEC0) (Int -> TextBuilder) -> Int -> TextBuilder
forall a b. (a -> b) -> a -> b
$ Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
second
else if Word8 -> Bool
isAsciiByte Word8
second
then Word8 -> StateT (Confidence, ()) (Parser ByteString) ()
forall (m :: * -> *) stream token.
MonadParser m stream token =>
token -> m ()
push Word8
second StateT (Confidence, ()) (Parser ByteString) ()
-> TextBuilder -> TextBuilder
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Word8 -> TextBuilder
forall state. Word8 -> StateTextBuilder state
decoderFailure1 Word8
0x8E
else [Word8] -> TextBuilder
forall state. [Word8] -> StateTextBuilder state
decoderFailure [Word8
0x8E, Word8
second]
, (Word8 -> Bool)
-> TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0x8F) (TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String))
-> TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall a b. (a -> b) -> a -> b
$ do
Word8
second <- StateT (Confidence, ()) (Parser ByteString) Word8
forall (m :: * -> *) stream token.
MonadParser m stream token =>
m token
next
if Word8 -> Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> a -> Bool
range Word8
0xA1 Word8
0xFE Word8
second
then Bool -> Word8 -> TextBuilder
decodeSecond Bool
True Word8
second
else if Word8 -> Bool
isAsciiByte Word8
second
then Word8 -> StateT (Confidence, ()) (Parser ByteString) ()
forall (m :: * -> *) stream token.
MonadParser m stream token =>
token -> m ()
push Word8
second StateT (Confidence, ()) (Parser ByteString) ()
-> TextBuilder -> TextBuilder
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Word8 -> TextBuilder
forall state. Word8 -> StateTextBuilder state
decoderFailure1 Word8
0x8F
else [Word8] -> TextBuilder
forall state. [Word8] -> StateTextBuilder state
decoderFailure [Word8
0x8F, Word8
second]
, (Word8 -> Bool)
-> (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> (test -> m out) -> SwitchCase test m out
If Word8 -> Bool
isAsciiByte Word8 -> TextBuilder
forall state. Word8 -> StateTextBuilder state
toUnicode1
, (Word8 -> Bool)
-> (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> (test -> m out) -> SwitchCase test m out
If (Word8 -> Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> a -> Bool
range Word8
0xA1 Word8
0xFE) ((Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String))
-> (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall a b. (a -> b) -> a -> b
$ Bool -> Word8 -> TextBuilder
decodeSecond Bool
False
, (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> m out) -> SwitchCase test m out
Else Word8 -> TextBuilder
forall state. Word8 -> StateTextBuilder state
decoderFailure1
]
decodeSecond :: Bool -> W.Word8 -> TextBuilder
decodeSecond :: Bool -> Word8 -> TextBuilder
decodeSecond Bool
is0212 Word8
lead = StateT (Confidence, ()) (Parser ByteString) Word8
forall (m :: * -> *) stream token.
MonadParser m stream token =>
m token
next StateT (Confidence, ()) (Parser ByteString) Word8
-> (Word8 -> TextBuilder) -> TextBuilder
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)]
-> Word8 -> TextBuilder
forall (m :: * -> *) test out.
Alternative m =>
[SwitchCase test m out] -> test -> m out
switch
[ (Word8 -> Bool)
-> (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> (test -> m out) -> SwitchCase test m out
If (Word8 -> Word8 -> Word8 -> Bool
forall a. Ord a => a -> a -> a -> Bool
range Word8
0xA1 Word8
0xFE) ((Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String))
-> (Word8 -> TextBuilder)
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall a b. (a -> b) -> a -> b
$ \Word8
trail ->
TextBuilder -> (Char -> TextBuilder) -> Maybe Char -> TextBuilder
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ([Word8] -> TextBuilder
forall state. [Word8] -> StateTextBuilder state
decoderFailure ([Word8] -> TextBuilder) -> [Word8] -> TextBuilder
forall a b. (a -> b) -> a -> b
$ [Word8]
bs [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
trail]) ([Word8] -> Char -> TextBuilder
forall state. [Word8] -> Char -> StateTextBuilder state
emit ([Word8] -> Char -> TextBuilder) -> [Word8] -> Char -> TextBuilder
forall a b. (a -> b) -> a -> b
$ [Word8]
bs [Word8] -> [Word8] -> [Word8]
forall a. [a] -> [a] -> [a]
++ [Word8
trail]) (Maybe Char -> TextBuilder)
-> (Word -> Maybe Char) -> Word -> TextBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Maybe Char
decodeIndex (Word -> TextBuilder) -> Word -> TextBuilder
forall a b. (a -> b) -> a -> b
$
(Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
lead Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
0xA1) Word -> Word -> Word
forall a. Num a => a -> a -> a
* Word
94 Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
trail Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
0xA1
, (Word8 -> Bool)
-> TextBuilder
-> SwitchCase
Word8
(StateT (Confidence, ()) (Parser ByteString))
(DecoderError String)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
isAsciiByte) TextBuilder
forall (f :: * -> *) a. Alternative f => f a
A.empty
]
where (Word -> Maybe Char
decodeIndex, [Word8]
bs)
| Bool
is0212 = (Word -> Maybe Char
decodeIndex0212, [Word8
0x8F, Word8
lead])
| Bool
otherwise = (Word -> Maybe Char
decodeIndex0208, [Word8
lead])
encoder :: BinaryBuilder
encoder :: BinaryBuilder
encoder = StateT () (Parser Text) Char
forall (m :: * -> *) stream token.
MonadParser m stream token =>
m token
next StateT () (Parser Text) Char
-> (Char -> BinaryBuilder) -> BinaryBuilder
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)]
-> Char -> BinaryBuilder
forall (m :: * -> *) test out.
Alternative m =>
[SwitchCase test m out] -> test -> m out
switch
[ (Char -> Bool)
-> (Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> Bool) -> (test -> m out) -> SwitchCase test m out
If Char -> Bool
C.isAscii Char -> BinaryBuilder
forall state. Char -> StateBinaryBuilder state
fromAscii
, (Char -> Bool)
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\xA5') (BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString))
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall a b. (a -> b) -> a -> b
$ EncoderError ShortByteString -> BinaryBuilder
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortByteString -> EncoderError ShortByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString -> EncoderError ShortByteString)
-> ShortByteString -> EncoderError ShortByteString
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
BS.SH.pack [Word8
0x5C])
, (Char -> Bool)
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\x203E') (BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString))
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall a b. (a -> b) -> a -> b
$ EncoderError ShortByteString -> BinaryBuilder
forall (m :: * -> *) a. Monad m => a -> m a
return (ShortByteString -> EncoderError ShortByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString -> EncoderError ShortByteString)
-> ShortByteString -> EncoderError ShortByteString
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
BS.SH.pack [Word8
0x7E])
, (Char -> Bool)
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> Bool) -> m out -> SwitchCase test m out
If_ (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\x2212') (BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString))
-> BinaryBuilder
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall a b. (a -> b) -> a -> b
$ Maybe Char -> Char -> BinaryBuilder
encodeTwoByte (Char -> Maybe Char
forall a. a -> Maybe a
Just Char
'\x2212') Char
'\xFF0D'
, (Char -> Bool)
-> (Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> Bool) -> (test -> m out) -> SwitchCase test m out
If (Char -> Char -> Char -> Bool
forall a. Ord a => a -> a -> a -> Bool
range Char
'\xFF61' Char
'\xFF9F') ((Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString))
-> (Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall a b. (a -> b) -> a -> b
$ \Char
char ->
EncoderError ShortByteString -> BinaryBuilder
forall (m :: * -> *) a. Monad m => a -> m a
return (EncoderError ShortByteString -> BinaryBuilder)
-> (ShortByteString -> EncoderError ShortByteString)
-> ShortByteString
-> BinaryBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> EncoderError ShortByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString -> BinaryBuilder)
-> ShortByteString -> BinaryBuilder
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
BS.SH.pack [Word8
0x8E, Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> Int -> Word8
forall a b. (a -> b) -> a -> b
$ Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
char Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
0xFEC0]
, (Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall test (m :: * -> *) out.
(test -> m out) -> SwitchCase test m out
Else ((Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString))
-> (Char -> BinaryBuilder)
-> SwitchCase
Char (StateT () (Parser Text)) (EncoderError ShortByteString)
forall a b. (a -> b) -> a -> b
$ Maybe Char -> Char -> BinaryBuilder
encodeTwoByte Maybe Char
forall a. Maybe a
Nothing
]
encodeTwoByte :: Maybe Char -> Char -> BinaryBuilder
encodeTwoByte :: Maybe Char -> Char -> BinaryBuilder
encodeTwoByte Maybe Char
err Char
char = case Char -> Maybe Word
encodeIndex0208 Char
char of
Just Word
index ->
let (Word
lead, Word
trail) = Word -> Word -> (Word, Word)
forall a. Integral a => a -> a -> (a, a)
divMod Word
index Word
94
in EncoderError ShortByteString -> BinaryBuilder
forall (m :: * -> *) a. Monad m => a -> m a
return (EncoderError ShortByteString -> BinaryBuilder)
-> (ShortByteString -> EncoderError ShortByteString)
-> ShortByteString
-> BinaryBuilder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> EncoderError ShortByteString
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ShortByteString -> BinaryBuilder)
-> ShortByteString -> BinaryBuilder
forall a b. (a -> b) -> a -> b
$ [Word8] -> ShortByteString
BS.SH.pack [Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
lead Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
0xA1, Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
trail Word8 -> Word8 -> Word8
forall a. Num a => a -> a -> a
+ Word8
0xA1]
Maybe Word
Nothing -> Char -> BinaryBuilder
forall state out. Char -> StateEncoder state (EncoderError out)
encoderFailure (Char -> BinaryBuilder) -> Char -> BinaryBuilder
forall a b. (a -> b) -> a -> b
$ Char -> Maybe Char -> Char
forall a. a -> Maybe a -> a
Y.fromMaybe Char
char Maybe Char
err
decodeIndex0208 :: Word -> Maybe Char
decodeIndex0208 :: Word -> Maybe Char
decodeIndex0208 Word
index =
IO (MemoizationTable Word (Maybe Char))
-> Maybe (IO (MemoizationTable Char (Maybe Word)))
-> Word
-> (Word -> Maybe Char)
-> Maybe Char
forall k v.
(Eq k, Hashable k, Eq v, Hashable v) =>
IO (MemoizationTable k (Maybe v))
-> Maybe (IO (MemoizationTable v (Maybe k)))
-> k
-> (k -> Maybe v)
-> Maybe v
lookupMemoizedIndex IO (MemoizationTable Word (Maybe Char))
decodeIndex0208M (IO (MemoizationTable Char (Maybe Word))
-> Maybe (IO (MemoizationTable Char (Maybe Word)))
forall a. a -> Maybe a
Just IO (MemoizationTable Char (Maybe Word))
encodeIndex0208M) Word
index Word -> Maybe Char
readDecodeIndex0208
decodeIndex0208M :: DecoderMemoTable
decodeIndex0208M :: IO (MemoizationTable Word (Maybe Char))
decodeIndex0208M = IO (MemoizationTable Word (Maybe Char))
forall k v. IO (MemoizationTable k v)
newMemoizationTable
{-# NOINLINE decodeIndex0208M #-}
readDecodeIndex0208 :: Word -> Maybe Char
readDecodeIndex0208 :: Word -> Maybe Char
readDecodeIndex0208 Word
index = Word -> [(Word, Char)] -> Maybe Char
forall k v. Ord k => k -> [(k, v)] -> Maybe v
search Word
index ([(Word, Char)] -> Maybe Char) -> [(Word, Char)] -> Maybe Char
forall a b. (a -> b) -> a -> b
$ String -> [(Word, Char)]
loadIndex String
"jis0208"
decodeIndex0212 :: Word -> Maybe Char
decodeIndex0212 :: Word -> Maybe Char
decodeIndex0212 Word
index = IO (MemoizationTable Word (Maybe Char))
-> Maybe (IO (MemoizationTable Char (Maybe Word)))
-> Word
-> (Word -> Maybe Char)
-> Maybe Char
forall k v.
(Eq k, Hashable k, Eq v, Hashable v) =>
IO (MemoizationTable k (Maybe v))
-> Maybe (IO (MemoizationTable v (Maybe k)))
-> k
-> (k -> Maybe v)
-> Maybe v
lookupMemoizedIndex IO (MemoizationTable Word (Maybe Char))
decodeIndex0212M Maybe (IO (MemoizationTable Char (Maybe Word)))
forall a. Maybe a
Nothing Word
index Word -> Maybe Char
readDecodeIndex0212
decodeIndex0212M :: DecoderMemoTable
decodeIndex0212M :: IO (MemoizationTable Word (Maybe Char))
decodeIndex0212M = IO (MemoizationTable Word (Maybe Char))
forall k v. IO (MemoizationTable k v)
newMemoizationTable
{-# NOINLINE decodeIndex0212M #-}
readDecodeIndex0212 :: Word -> Maybe Char
readDecodeIndex0212 :: Word -> Maybe Char
readDecodeIndex0212 Word
index = Word -> [(Word, Char)] -> Maybe Char
forall k v. Ord k => k -> [(k, v)] -> Maybe v
search Word
index ([(Word, Char)] -> Maybe Char) -> [(Word, Char)] -> Maybe Char
forall a b. (a -> b) -> a -> b
$ String -> [(Word, Char)]
loadIndex String
"jis0212"
encodeIndex0208 :: Char -> Maybe Word
encodeIndex0208 :: Char -> Maybe Word
encodeIndex0208 Char
char =
IO (MemoizationTable Char (Maybe Word))
-> Maybe (IO (MemoizationTable Word (Maybe Char)))
-> Char
-> (Char -> Maybe Word)
-> Maybe Word
forall k v.
(Eq k, Hashable k, Eq v, Hashable v) =>
IO (MemoizationTable k (Maybe v))
-> Maybe (IO (MemoizationTable v (Maybe k)))
-> k
-> (k -> Maybe v)
-> Maybe v
lookupMemoizedIndex IO (MemoizationTable Char (Maybe Word))
encodeIndex0208M (IO (MemoizationTable Word (Maybe Char))
-> Maybe (IO (MemoizationTable Word (Maybe Char)))
forall a. a -> Maybe a
Just IO (MemoizationTable Word (Maybe Char))
decodeIndex0208M) Char
char Char -> Maybe Word
readEncodeIndex0208
encodeIndex0208M :: EncoderMemoTable
encodeIndex0208M :: IO (MemoizationTable Char (Maybe Word))
encodeIndex0208M = IO (MemoizationTable Char (Maybe Word))
forall k v. IO (MemoizationTable k v)
newMemoizationTable
{-# NOINLINE encodeIndex0208M #-}
readEncodeIndex0208 :: Char -> Maybe Word
readEncodeIndex0208 :: Char -> Maybe Word
readEncodeIndex0208 Char
char = Char -> [(Char, Word)] -> Maybe Word
forall k v. Ord k => k -> [(k, v)] -> Maybe v
search Char
char ([(Char, Word)] -> Maybe Word)
-> ([(Word, Char)] -> [(Char, Word)])
-> [(Word, Char)]
-> Maybe Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Word, Char) -> (Char, Word)) -> [(Word, Char)] -> [(Char, Word)]
forall a b. (a -> b) -> [a] -> [b]
map (Word, Char) -> (Char, Word)
forall a b. (a, b) -> (b, a)
U.swap ([(Word, Char)] -> Maybe Word) -> [(Word, Char)] -> Maybe Word
forall a b. (a -> b) -> a -> b
$ String -> [(Word, Char)]
loadIndex String
"jis0208"