{-# LANGUAGE OverloadedStrings #-}

module Data.ISBN.ISBN10
    ( ISBN(..)
    , validateISBN10
      -- * Validation Errors
    , ISBN10ValidationError(..)
    , renderISBN10ValidationError
      -- * Helpers
    , confirmISBN10CheckDigit
    , calculateISBN10CheckDigitValue
    , isbn10CharToNumericValue
    , numericValueToISBN10Char
    , isValidISBN10CheckDigit
    , isNumericCharacter
    , isISBN10
      -- * Unsafe Coercion
    , unsafeToISBN10
    ) where

import           Control.Monad
import           Data.Char
import           Data.Text       ( Text )
import qualified Data.Text       as Text

import           Data.ISBN.Types ( ISBN (ISBN10) )



-- | Used to safely create 'ISBN10' values represented by the 'ISBN' data type.
-- Assumes that the 'Data.Text.Text' input is an ISBN-10 string, either with or
-- without hyphens.
--
-- Will return either a validated ISBN-10 or an 'ISBN10ValidationError', which can be
-- rendered as a descriptive string using 'renderISBN10ValidationError'.
--
-- /Examples:/
--
-- @
-- validateISBN10 "0-345-81602-1" == Right (ISBN10 "0345816021")
-- validateISBN10 "0345816021"    == Right (ISBN10 "0345816021")
-- validateISBN10 "0-807-01429-X" == Right (ISBN10 "080701429X")
-- validateISBN10 "0-345-816"     == Left ISBN10InvalidInputLength
-- validateISBN10 "X-345-81602-1" == Left ISBN10IllegalCharactersInBody
-- validateISBN10 "0-345-81602-B" == Left ISBN10IllegalCharacterAsCheckDigit
-- validateISBN10 "0-345-81602-3" == Left ISBN10InvalidCheckDigit
-- @
validateISBN10 :: Text -> Either ISBN10ValidationError ISBN
validateISBN10 :: Text -> Either ISBN10ValidationError ISBN
validateISBN10 Text
input = do
    -- Make a copy of the text input before further manipulation to prevent
    -- space leaks if input text is a slice of a larger string
    let inputWithoutHyphens :: Text
inputWithoutHyphens = (Char -> Bool) -> Text -> Text
Text.filter (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'-') (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
Text.copy Text
input

    Bool
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Int
Text.length Text
inputWithoutHyphens Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
10) (Either ISBN10ValidationError ()
 -> Either ISBN10ValidationError ())
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall a b. (a -> b) -> a -> b
$
        ISBN10ValidationError -> Either ISBN10ValidationError ()
forall a b. a -> Either a b
Left ISBN10ValidationError
ISBN10InvalidInputLength

    let invalidBodyCharacters :: Text
invalidBodyCharacters = (Char -> Bool) -> Text -> Text
Text.filter (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isNumericCharacter) (Text -> Text
Text.init Text
inputWithoutHyphens)

    Bool
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Int
Text.length Text
invalidBodyCharacters Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (Either ISBN10ValidationError ()
 -> Either ISBN10ValidationError ())
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall a b. (a -> b) -> a -> b
$
        ISBN10ValidationError -> Either ISBN10ValidationError ()
forall a b. a -> Either a b
Left ISBN10ValidationError
ISBN10IllegalCharactersInBody

    Bool
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Char -> Bool
isValidISBN10CheckDigit (Char -> Bool) -> Char -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Char
Text.last Text
inputWithoutHyphens) (Either ISBN10ValidationError ()
 -> Either ISBN10ValidationError ())
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall a b. (a -> b) -> a -> b
$
        ISBN10ValidationError -> Either ISBN10ValidationError ()
forall a b. a -> Either a b
Left ISBN10ValidationError
ISBN10IllegalCharacterAsCheckDigit

    Bool
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text -> Bool
confirmISBN10CheckDigit Text
inputWithoutHyphens) (Either ISBN10ValidationError ()
 -> Either ISBN10ValidationError ())
-> Either ISBN10ValidationError ()
-> Either ISBN10ValidationError ()
forall a b. (a -> b) -> a -> b
$
        ISBN10ValidationError -> Either ISBN10ValidationError ()
forall a b. a -> Either a b
Left ISBN10ValidationError
ISBN10InvalidCheckDigit

    ISBN -> Either ISBN10ValidationError ISBN
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ISBN -> Either ISBN10ValidationError ISBN)
-> ISBN -> Either ISBN10ValidationError ISBN
forall a b. (a -> b) -> a -> b
$ Text -> ISBN
ISBN10 Text
inputWithoutHyphens



-- | Possible validation errors resulting from ISBN-10 validation.
data ISBN10ValidationError
    = ISBN10InvalidInputLength           -- ^ The length of the input string is not 10 characters, not counting hyphens
    | ISBN10IllegalCharactersInBody      -- ^ The first nine characters of the ISBN-10 input contain non-numeric characters
    | ISBN10IllegalCharacterAsCheckDigit -- ^ The check digit of the ISBN-10 is not a valid character (@0-9@ or @\'X\'@)
    | ISBN10InvalidCheckDigit            -- ^ The check digit is not valid for the given ISBN-10
    deriving (Int -> ISBN10ValidationError -> ShowS
[ISBN10ValidationError] -> ShowS
ISBN10ValidationError -> String
(Int -> ISBN10ValidationError -> ShowS)
-> (ISBN10ValidationError -> String)
-> ([ISBN10ValidationError] -> ShowS)
-> Show ISBN10ValidationError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ISBN10ValidationError] -> ShowS
$cshowList :: [ISBN10ValidationError] -> ShowS
show :: ISBN10ValidationError -> String
$cshow :: ISBN10ValidationError -> String
showsPrec :: Int -> ISBN10ValidationError -> ShowS
$cshowsPrec :: Int -> ISBN10ValidationError -> ShowS
Show, ISBN10ValidationError -> ISBN10ValidationError -> Bool
(ISBN10ValidationError -> ISBN10ValidationError -> Bool)
-> (ISBN10ValidationError -> ISBN10ValidationError -> Bool)
-> Eq ISBN10ValidationError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ISBN10ValidationError -> ISBN10ValidationError -> Bool
$c/= :: ISBN10ValidationError -> ISBN10ValidationError -> Bool
== :: ISBN10ValidationError -> ISBN10ValidationError -> Bool
$c== :: ISBN10ValidationError -> ISBN10ValidationError -> Bool
Eq)


-- | Convert an 'ISBN10ValidationError' into a human-friendly error message.
renderISBN10ValidationError :: ISBN10ValidationError -> Text
renderISBN10ValidationError :: ISBN10ValidationError -> Text
renderISBN10ValidationError ISBN10ValidationError
validationError =
    case ISBN10ValidationError
validationError of
        ISBN10ValidationError
ISBN10InvalidInputLength ->
            Text
"An ISBN-10 must be 10 characters, not counting hyphens"

        ISBN10ValidationError
ISBN10IllegalCharactersInBody ->
            Text
"The first nine characters of an ISBN-10 must all be numbers"

        ISBN10ValidationError
ISBN10IllegalCharacterAsCheckDigit ->
            Text
"The last character of the supplied ISBN-10 must be a number or the letter 'X'"

        ISBN10ValidationError
ISBN10InvalidCheckDigit ->
            Text
"The supplied ISBN-10 is not valid"


-- | Confirms that the check digit of an ISBN-10 is correct. Assumes that the
-- input consists of 9 numeric characters followed by a legal check digit
-- character (@0-9@ or @X@).
--
-- /Examples:/
--
-- @
-- confirmISBN10CheckDigit "0345816021" == True
-- confirmISBN10CheckDigit "080701429X" == True
-- @
confirmISBN10CheckDigit :: Text -> Bool
confirmISBN10CheckDigit :: Text -> Bool
confirmISBN10CheckDigit Text
isbn10 =
    Text -> Int
calculateISBN10CheckDigitValue (Text -> Text
Text.init Text
isbn10) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Char -> Int
isbn10CharToNumericValue (Text -> Char
Text.last Text
isbn10)


-- | Calculates an ISBN-10 check digit value using the standard check digit
-- calculation formula. Assumes that the input is 9 numeric characters. The
-- check digit value can be any number in the range 0 to 10, the last of
-- which is represented by the symbol \'X\' in an ISBN-10.
--
-- See: <https://en.wikipedia.org/wiki/International_Standard_Book_Number#ISBN-10_check_digits>
--
-- /Examples:/
--
-- @
-- calculateISBN10CheckDigitValue "034581602" == 1
-- calculateISBN10CheckDigitValue "080701429" == 10
-- @
calculateISBN10CheckDigitValue :: Text -> Int
calculateISBN10CheckDigitValue :: Text -> Int
calculateISBN10CheckDigitValue Text
input =
    Int -> String -> Int -> Int
go Int
10 (Text -> String
Text.unpack Text
input) Int
0
      where
        go :: Int -> String -> Int -> Int
go Int
n String
charList Int
acc =
            case String
charList of
              []      -> (Int
11 Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
acc Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
11)) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
11
              Char
c:String
clist -> Int -> String -> Int -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) String
clist (Int
acc Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Char -> Int
isbn10CharToNumericValue Char
c Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
n)


-- | Converts an ISBN-10 character to a numeric value. Valid input characters
-- include @0-9@ as well as @X@.
isbn10CharToNumericValue :: Char -> Int
isbn10CharToNumericValue :: Char -> Int
isbn10CharToNumericValue Char
'X' = Int
10
isbn10CharToNumericValue  Char
c  = Char -> Int
digitToInt Char
c

-- | Converts a numeric value to an ISBN-10 character. Valid input values
-- are the numbers from 0 to 10.
numericValueToISBN10Char :: Int -> Char
numericValueToISBN10Char :: Int -> Char
numericValueToISBN10Char Int
10 = Char
'X'
numericValueToISBN10Char Int
c  = Text -> Char
Text.head (Text -> Char) -> Text -> Char
forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
c


-- | Validates a character as a valid ISBN-10 check digit character.  ISBN-10
-- check digit characters include @0-9@ as well as the symbol @'X'@. The lowercase
-- letter \'x\' is not considered valid.
isValidISBN10CheckDigit :: Char -> Bool
isValidISBN10CheckDigit :: Char -> Bool
isValidISBN10CheckDigit Char
char = Char
char Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"1234567890X" :: String)

-- | Determines whether a character is numeric (e.g. in the range of @0-9@).
isNumericCharacter :: Char -> Bool
isNumericCharacter :: Char -> Bool
isNumericCharacter Char
char = Char
char Char -> String -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` (String
"1234567890" :: String)

-- | Determines whether an 'ISBN' value is an ISBN-10.
--
-- /Examples:/
--
-- @
-- isISBN10 (unsafeToISBN10 "0060899220")    == True
-- isISBN10 (unsafeToISBN13 "9780060899226") == False
-- @
--
-- /Since: 1.1.0.0/
isISBN10 :: ISBN -> Bool
isISBN10 :: ISBN -> Bool
isISBN10 (ISBN10 Text
_) = Bool
True
isISBN10 ISBN
_          = Bool
False


-- | Will create an 'ISBN10' value without any validation.
unsafeToISBN10 :: Text -> ISBN
unsafeToISBN10 :: Text -> ISBN
unsafeToISBN10 = Text -> ISBN
ISBN10