kanji-3.4.0: Perform 漢字検定 (Japan Kanji Aptitude Test) level analysis on Japanese Kanji

Copyright(c) Colin Woodbury 2015 2016
LicenseGPL3
MaintainerColin Woodbury <colingw@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Kanji.Types

Description

Types for this library. While a constructor for Kanji is made available here, you should prefer the kanji "smart constructor" unless you know for sure that the Char in question falls within the correct UTF8 range.

Synopsis

Documentation

newtype Kanji Source #

A single symbol of Kanji. Japanese Kanji were borrowed from China over several waves during the last 1,500 years. Japan names 2,136 of these as their standard set, with rarer characters being the domain of academia and esoteric writers.

Japanese has several Japan-only Kanji, including:

  • 畑 (a type of rice field)
  • 峠 (a narrow mountain pass)
  • 働 (to do physical labour)

Constructors

Kanji Char 

Instances

Eq Kanji Source # 

Methods

(==) :: Kanji -> Kanji -> Bool #

(/=) :: Kanji -> Kanji -> Bool #

Ord Kanji Source # 

Methods

compare :: Kanji -> Kanji -> Ordering #

(<) :: Kanji -> Kanji -> Bool #

(<=) :: Kanji -> Kanji -> Bool #

(>) :: Kanji -> Kanji -> Bool #

(>=) :: Kanji -> Kanji -> Bool #

max :: Kanji -> Kanji -> Kanji #

min :: Kanji -> Kanji -> Kanji #

Show Kanji Source # 

Methods

showsPrec :: Int -> Kanji -> ShowS #

show :: Kanji -> String #

showList :: [Kanji] -> ShowS #

Generic Kanji Source # 

Associated Types

type Rep Kanji :: * -> * #

Methods

from :: Kanji -> Rep Kanji x #

to :: Rep Kanji x -> Kanji #

Hashable Kanji Source # 

Methods

hashWithSalt :: Int -> Kanji -> Int #

hash :: Kanji -> Int #

ToJSON Kanji Source # 
FromJSON Kanji Source # 
NFData Kanji Source # 

Methods

rnf :: Kanji -> () #

type Rep Kanji Source # 
type Rep Kanji = D1 * (MetaData "Kanji" "Data.Kanji.Types" "kanji-3.4.0-L0VL7q7DKEnE6ivNv9fxO3" True) (C1 * (MetaCons "Kanji" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Char)))

_kanji :: Kanji -> Char Source #

The original Char of a Kanji.

kanji :: Char -> Maybe Kanji Source #

Construct a Kanji value from some Char if it falls in the correct UTF8 range.

data Level Source #

A Level or Kyuu (級) of Japanese Kanji ranking. There are 12 of these, from 10 to 1, including intermediate levels between 3 and 2, and 2 and 1.

Japanese students will typically have Level-5 ability by the time they finish elementary school. Level-5 accounts for 1,006 characters.

By the end of middle school, they would have covered up to Level-3 (1607 Kanji) in their Japanese class curriculum.

While Level-2 (2,136 Kanji) is considered "standard adult" ability, many adults could not pass the Level-2, or even the Level-Pre2 (1940 Kanji) exam without considerable study.

Level data for Kanji above Level-2 is currently not provided by this library.

Instances

Enum Level Source # 
Eq Level Source # 

Methods

(==) :: Level -> Level -> Bool #

(/=) :: Level -> Level -> Bool #

Ord Level Source # 

Methods

compare :: Level -> Level -> Ordering #

(<) :: Level -> Level -> Bool #

(<=) :: Level -> Level -> Bool #

(>) :: Level -> Level -> Bool #

(>=) :: Level -> Level -> Bool #

max :: Level -> Level -> Level #

min :: Level -> Level -> Level #

Show Level Source # 

Methods

showsPrec :: Int -> Level -> ShowS #

show :: Level -> String #

showList :: [Level] -> ShowS #

Generic Level Source # 

Associated Types

type Rep Level :: * -> * #

Methods

from :: Level -> Rep Level x #

to :: Rep Level x -> Level #

Hashable Level Source # 

Methods

hashWithSalt :: Int -> Level -> Int #

hash :: Level -> Int #

ToJSON Level Source # 
ToJSONKey Level Source # 
FromJSON Level Source # 
NFData Level Source # 

Methods

rnf :: Level -> () #

type Rep Level Source # 
type Rep Level = D1 * (MetaData "Level" "Data.Kanji.Types" "kanji-3.4.0-L0VL7q7DKEnE6ivNv9fxO3" False) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Ten" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Nine" PrefixI False) (U1 *)) (C1 * (MetaCons "Eight" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "Seven" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Six" PrefixI False) (U1 *)) (C1 * (MetaCons "Five" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Four" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Three" PrefixI False) (U1 *)) (C1 * (MetaCons "PreTwo" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Two" PrefixI False) (U1 *)) (C1 * (MetaCons "PreOne" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "One" PrefixI False) (U1 *)) (C1 * (MetaCons "Unknown" PrefixI False) (U1 *))))))

isKanji :: Char -> Bool Source #

Legal Kanji appear between UTF-8 characters 19968 and 40959.

isHiragana :: Char -> Bool Source #

あ to ん.

isKatakana :: Char -> Bool Source #

ア to ン.

data CharCat Source #

General categories for characters, at least as is useful for thinking about Japanese.

Japanese "full-width" numbers and letters will be counted as Numeral and RomanLetter respectively, alongside their usual ASCII forms.

Instances

Eq CharCat Source # 

Methods

(==) :: CharCat -> CharCat -> Bool #

(/=) :: CharCat -> CharCat -> Bool #

Ord CharCat Source # 
Show CharCat Source # 
Generic CharCat Source # 

Associated Types

type Rep CharCat :: * -> * #

Methods

from :: CharCat -> Rep CharCat x #

to :: Rep CharCat x -> CharCat #

Hashable CharCat Source # 

Methods

hashWithSalt :: Int -> CharCat -> Int #

hash :: CharCat -> Int #

ToJSON CharCat Source # 
ToJSONKey CharCat Source # 
FromJSON CharCat Source # 
NFData CharCat Source # 

Methods

rnf :: CharCat -> () #

type Rep CharCat Source # 
type Rep CharCat = D1 * (MetaData "CharCat" "Data.Kanji.Types" "kanji-3.4.0-L0VL7q7DKEnE6ivNv9fxO3" False) ((:+:) * ((:+:) * (C1 * (MetaCons "Hanzi" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Hiragana" PrefixI False) (U1 *)) (C1 * (MetaCons "Katakana" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Numeral" PrefixI False) (U1 *)) (C1 * (MetaCons "RomanLetter" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Punctuation" PrefixI False) (U1 *)) (C1 * (MetaCons "Other" PrefixI False) (U1 *)))))