about summary refs log tree commit diff
diff options
context:
space:
mode:
authorlukasepple <git@lukasepple.de>2015-11-01 00:21:45 +0100
committerlukasepple <git@lukasepple.de>2015-11-01 00:21:45 +0100
commitfc2a74fb470726d902ba90a2595a3acd21e572a9 (patch)
tree03455da64528517993fd9d69135337a188b313a4
parent9869e5095800766622170d0a18ce8693efeca63c (diff)
Add documentation for all existing modules.
* Text.Emoji.DataParser Coverage 100%
* Text.Emoji.Types Coverage 100%
-rw-r--r--src/Text/Emoji/DataParser.hs30
-rw-r--r--src/Text/Emoji/Types.hs51
2 files changed, 68 insertions, 13 deletions
diff --git a/src/Text/Emoji/DataParser.hs b/src/Text/Emoji/DataParser.hs
index 900e9e7..e0efd2f 100644
--- a/src/Text/Emoji/DataParser.hs
+++ b/src/Text/Emoji/DataParser.hs
@@ -1,3 +1,13 @@
+{-|
+  Module:      Text.Emoji.DataParser
+  Description: Parser for the emoji-data file format
+
+This module defines the Parsec parser necessary
+to parse the emoji-data.txt file issued by the
+unicode consortium.
+-}
+
+
 {-# LANGUAGE OverloadedStrings #-}
 module Text.Emoji.DataParser where
 
@@ -12,18 +22,21 @@ import           Text.Parsec
 import           Text.Parsec.String
 import           Numeric             (readHex)
 
+-- | Parses the entire emoji-data.txt file.
+-- Left String is a comment line.
+-- Right Emoji is a line describing an emoji character.
 emojiDataFile :: Parser [Either String Emoji]
 emojiDataFile = many $ emojiCommentLine <|> emojiDataEntry
 
+-- | Parsers an comment line.
 emojiCommentLine :: Parser (Either String Emoji)
-emojiCommentLine = Left <$> emojiComment
-
-emojiComment :: Parser String
-emojiComment = do
+emojiCommentLine = do
   string "#"
   r <- manyTill anyChar (try lineTerminated)
-  return r
+  return $ Left r
 
+-- | Parsers an emoji data entry and returns a
+-- Left Emoji using all the information given.
 emojiDataEntry :: Parser (Either String Emoji)
 emojiDataEntry = do
   code <- fst . head . readHex . filter (not . isSpace) <$> field hexDigit
@@ -48,18 +61,25 @@ emojiDataEntry = do
     , _version        = name
     }
 
+-- | Parses the emoji sources field.
+-- TODO: Handle NA correctly (no problem right now though).
 sources :: Parser EmojiSources
 sources = catMaybes .
   map (flip lookup (emojiSources)) .
   splitOn " " . dropAround isSpace <$>
   many (oneOf (map (head . fst) emojiSources) <|> char ' ')
 
+-- | Matches the separator sequence.
 separator :: Parser String
 separator = string ";\t" <|> string " ;\t"
 
+-- | Uses a parser association list to convert
+-- to a sum type.
 sumType :: ParserAssoc a -> Parser a
 sumType assocs = choice [r <$ (try . string $ s) | (s,r) <- assocs]
 
+-- | Identical to sumType except that it matches
+-- a separator afterwards.
 sumTypeField :: ParserAssoc a -> Parser a
 sumTypeField assocs = do
   res <- sumType assocs
diff --git a/src/Text/Emoji/Types.hs b/src/Text/Emoji/Types.hs
index c2040bb..6acca16 100644
--- a/src/Text/Emoji/Types.hs
+++ b/src/Text/Emoji/Types.hs
@@ -1,20 +1,34 @@
+{-|
+  Module:      Text.Emoji.Types
+  Description: Basic types and abstractions of emoji
+-}
+
+
 {-# LANGUAGE TemplateHaskell #-}
 module Text.Emoji.Types where
 
 import           Data.Char (toLower)
 import           GHC.Word  (Word64 ())
 
+-- | Represents the default style
+-- an emoji is displayed as.
+-- See http://www.unicode.org/reports/tr51/index.html#Emoji_vs_Text_Display
 data EmojiStyle
   = Emoji
   | Text
   deriving Show
 
+-- | Describes how common an emoji is.
+-- See http://www.unicode.org/reports/tr51/index.html#Emoji_Levels
 data EmojiLevel
   = L1
   | L2
   | NA
   deriving Show
 
+-- | Describes if and how the emoji can be
+-- used as modifier.
+-- See: http://www.unicode.org/reports/tr51/index.html#Emoji_Modifiers
 data EmojiModifierStatus
   = Modifier
   | Primary
@@ -22,6 +36,11 @@ data EmojiModifierStatus
   | None
   deriving (Show)
 
+-- | Represents the source(s) the emoji came from.
+-- The Unicode standard created an universal encoding
+-- for different already existing symbols and characters.
+-- For example Wingdings symbols were added to the Unicode emojis.
+-- See http://www.unicode.org/reports/tr51/#Major_Sources
 data EmojiSource
   = ZDings
   | ARIB
@@ -30,32 +49,48 @@ data EmojiSource
   | X -- FIXME: Long Name?
   deriving (Show)
 
+-- | An associative list to hold relations
+-- between a string and an element of type a
+-- in order to convert strings into as.
 type ParserAssoc a = [(String, a)]
 
+-- | Automatically generate an association tuple by
+-- using show. Addtionally the result of show is applied to
+-- f to do corrections of the derived show output.
 tupleShow :: Show a => (String -> String) -> a -> (String, a)
 tupleShow f x = (f . show $ x, x)
 
+-- | Parser association list for EmojiStyle
 emojiStyles :: ParserAssoc EmojiStyle
 emojiStyles = map (tupleShow $ map toLower) [Emoji, Text]
 
+-- | Parser association list for EmojiLevel
 emojiLevels :: ParserAssoc EmojiLevel
 emojiLevels = map (tupleShow id) [L1, L2, NA]
 
+-- | Parser association list for EmojiModifierStatus
 emojiModifierStati :: ParserAssoc EmojiModifierStatus
-emojiModifierStati = map (tupleShow $ map toLower) [Modifier, Primary, Secondary, None]
+emojiModifierStati = map (tupleShow $ map toLower)
+  [Modifier, Primary, Secondary, None]
 
+-- | Parser association list for EmojiSource
 emojiSources :: ParserAssoc EmojiSource
 emojiSources = [ ("z", ZDings), ("a", ARIB), ("j", JCarrier), ("w", WDings)
                , ("x", X) ]
 
+-- | Since a Emoji might come from multiple sources
+-- these are represented as a list of EmojiSource.
+-- Empty List means 'NA' (not applicable).
 type EmojiSources = [EmojiSource]
 
+-- | Emoji holds all the information about an
+-- emoji provided by emoji-data.txt
 data Emoji = MkEmoji
-  { _code          :: Word64
-  , _defaultStyle  :: EmojiStyle
-  , _emojiLevel    :: EmojiLevel
-  , _emojiModifier :: EmojiModifierStatus
-  , _emojiSources  :: EmojiSources
-  , _version       :: String
-  , _name          :: String
+  { _code          :: Word64              -- ^ The code of the unicode character.
+  , _defaultStyle  :: EmojiStyle          -- ^ The default display style.
+  , _emojiLevel    :: EmojiLevel          -- ^ Commonness for the character.
+  , _emojiModifier :: EmojiModifierStatus -- ^ Wether the emoji is a modifier.
+  , _emojiSources  :: EmojiSources        -- ^ Where the emoji originates.
+  , _version       :: String              -- ^ Version the character was introduced.
+  , _name          :: String              -- ^ The Name of the character
   } deriving Show