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

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

Data.Kanji

Contents

Description

A library for analysing the density of Kanji in given texts, according to their Level classification, as defined by the Japan Kanji Aptitude Testing Foundation (日本漢字能力検定協会).

Synopsis

Kanji

data 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)

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.1.0.1-G2K6XyiD6hiLlm25DD7LVV" True) (C1 * (MetaCons "Kanji" PrefixI True) (S1 * (MetaSel (Just Symbol "_kanji") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Char)))

kanji :: Char -> Maybe Kanji Source #

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

_kanji :: Kanji -> Char Source #

The original Char of a Kanji.

allKanji :: Map Level (Set Kanji) Source #

All Japanese Kanji, grouped by their Level (級).

isKanji :: Char -> Bool Source #

Legal Kanji appear between UTF8 characters 19968 and 40959.

Levels

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.

Constructors

Ten 
Nine 
Eight 
Seven 
Six 
Five 
Four 
Three 
PreTwo 
Two 
PreOne 
One 

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.1.0.1-G2K6XyiD6hiLlm25DD7LVV" 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 *))))))

level :: Kanji -> Maybe Level Source #

What Level does a Kanji belong to?

Analysis

percentSpread :: [Kanji] -> Map Kanji Float Source #

The distribution of each Kanji in a set of them. The distribution values must sum to 1.

levelDist :: [Kanji] -> Map Level Float Source #

How much of each Level is represented by a group of Kanji? The distribution values will sum to <= 1.

averageLevel :: [Kanji] -> Float Source #

Find the average Level of a given set of Kanji.

uniques :: [Kanji] -> Map Level (Set Kanji) Source #

Which Kanji appeared from each Level in the text?

Densities

kanjiDensity :: Int -> [Kanji] -> Float Source #

Given the length of some String-like type and a list of Kanji found therein, what percentage of them were Kanji?

elementaryDen :: Map Level Float -> Float Source #

How much of the Kanji found are learnt in elementary school in Japan?

elementaryDen . levelDist :: [Kanji] -> Float

middleDen :: Map Level Float -> Float Source #

How much of the Kanji found are learnt by the end of middle school?

middleDen . levelDist :: [Kanji] -> Float

highDen :: Map Level Float -> Float Source #

How much of the Kanji found are learnt by the end of high school?

highDen . levelDist :: [Kanji] -> Float

adultDen :: Map Level Float -> Float Source #

How much of the Kanji found should be able to be read by the average person?

adultDen . levelDist :: [Kanji] -> Float