{-# LANGUAGE Safe #-}

-- |
-- Module      : Data.Char.Math.Serif.Greek
-- Description : Serif mathematical alphanumeric symbols
-- Maintainer  : hapytexeu+gh@gmail.com
-- Stability   : experimental
-- Portability : POSIX
--
-- See "Data.Char.Math" for further documentation.
module Data.Char.Math.Serif.Greek
  ( greekSerif,
    greekSerif',
    greekSerifNoBold,
    greekSerifNoBold',
    greekSerifBold,
    greekSerifBold',
    greekSerifNoItalic,
    greekSerifNoItalic',
    greekSerifItalic,
    greekSerifItalic',
    greekSerifNoBoldNoItalic,
    greekSerifNoBoldNoItalic',
    greekSerifBoldNoItalic,
    greekSerifBoldNoItalic',
    greekSerifNoBoldItalic,
    greekSerifNoBoldItalic',
    greekSerifBoldItalic,
    greekSerifBoldItalic',
  )
where

import Data.Char.Core (Emphasis, ItalicType, isGreek, splitEmphasis, splitItalicType)
import Data.Char.Math.Internal

-- | Convert the given character to a mathematical symbol with serifs, in the
-- given /emphasis/ and in the given /italics/ type wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerif ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerif :: ItalicType -> Emphasis -> Char -> Maybe Char
greekSerif = forall a. a -> a -> ItalicType -> a
splitItalicType Emphasis -> Char -> Maybe Char
greekSerifNoItalic Emphasis -> Char -> Maybe Char
greekSerifItalic

-- | Convert the given character to a mathematical symbol with serifs, with a
-- given /emphasis/ and a given /italics/ style. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerif' ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, depending on the given 'Emphasis' in bold or not, and depending on the given 'ItalicType' in italics or not.
  Char
greekSerif' :: ItalicType -> Emphasis -> Char -> Char
greekSerif' = forall a. a -> a -> ItalicType -> a
splitItalicType Emphasis -> Char -> Char
greekSerifNoItalic' Emphasis -> Char -> Char
greekSerifItalic'

-- | Convert the given character to a mathematical symbol with serifs, with no
-- /bold/ and no /italics/. This maps characters to itself.
greekSerifNoBoldNoItalic' ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, not in bold and not in italics.
  Char
greekSerifNoBoldNoItalic' :: Char -> Char
greekSerifNoBoldNoItalic' = forall a. a -> a
id

-- | Convert the given character to a mathematical symbol with serifs, with no
-- /bold/, and no /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifNoBoldNoItalic ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifNoBoldNoItalic :: Char -> Maybe Char
greekSerifNoBoldNoItalic = forall a b. (a -> Bool) -> (a -> b) -> a -> Maybe b
_withCondition Char -> Bool
isGreek Char -> Char
greekSerifNoBoldNoItalic'

-- | Convert the given character to a mathematical symbol with serifs, with no
-- /bold/ and in /italics/. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifNoBoldItalic' ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, not in bold and in italics.
  Char
greekSerifNoBoldItalic' :: Char -> Char
greekSerifNoBoldItalic' Char
'ϴ' = Char
'𝛳'
greekSerifNoBoldItalic' Char
'∇' = Char
'𝛻'
greekSerifNoBoldItalic' Char
'∂' = Char
'𝜕'
greekSerifNoBoldItalic' Char
'ϵ' = Char
'𝜖'
greekSerifNoBoldItalic' Char
'ϑ' = Char
'𝜗'
greekSerifNoBoldItalic' Char
'ϰ' = Char
'𝜘'
greekSerifNoBoldItalic' Char
'ϕ' = Char
'𝜙'
greekSerifNoBoldItalic' Char
'ϱ' = Char
'𝜚'
greekSerifNoBoldItalic' Char
'ϖ' = Char
'𝜛'
greekSerifNoBoldItalic' Char
c
  | Char
'Α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'Ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d351 Char
c
  | Char
'α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d34b Char
c
  | Bool
otherwise = Char
c

-- | Convert the given character to a mathematical symbol with serifs, with no
-- /bold/, and in /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifNoBoldItalic ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifNoBoldItalic :: Char -> Maybe Char
greekSerifNoBoldItalic = forall a b. (a -> Bool) -> (a -> b) -> a -> Maybe b
_withCondition Char -> Bool
isGreek Char -> Char
greekSerifNoBoldItalic'

-- | Convert the given character to a mathematical symbol with serifs, in /bold/
-- not in /italics/. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifBoldNoItalic' ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, in bold and not in italics.
  Char
greekSerifBoldNoItalic' :: Char -> Char
greekSerifBoldNoItalic' Char
'ϴ' = Char
'𝚹'
greekSerifBoldNoItalic' Char
'∇' = Char
'𝛁'
greekSerifBoldNoItalic' Char
'∂' = Char
'𝛛'
greekSerifBoldNoItalic' Char
'ϵ' = Char
'𝛜'
greekSerifBoldNoItalic' Char
'ϑ' = Char
'𝛝'
greekSerifBoldNoItalic' Char
'ϰ' = Char
'𝛞'
greekSerifBoldNoItalic' Char
'ϕ' = Char
'𝛟'
greekSerifBoldNoItalic' Char
'ϱ' = Char
'𝛠'
greekSerifBoldNoItalic' Char
'ϖ' = Char
'𝛡'
greekSerifBoldNoItalic' Char
c
  | Char
'Α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'Ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d317 Char
c
  | Char
'α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d311 Char
c
  | Bool
otherwise = Char
c

-- | Convert the given character to a mathematical symbol with serifs, in
-- /bold/, and no /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifBoldNoItalic ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifBoldNoItalic :: Char -> Maybe Char
greekSerifBoldNoItalic = forall a b. (a -> Bool) -> (a -> b) -> a -> Maybe b
_withCondition Char -> Bool
isGreek Char -> Char
greekSerifBoldNoItalic'

-- | Convert the given character to a mathematical symbol with serifs, with in
-- /bold/ and in /italics/. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifBoldItalic' ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, in bold and in italics.
  Char
greekSerifBoldItalic' :: Char -> Char
greekSerifBoldItalic' Char
'ϴ' = Char
'𝜭'
greekSerifBoldItalic' Char
'∇' = Char
'𝜵'
greekSerifBoldItalic' Char
'∂' = Char
'𝝏'
greekSerifBoldItalic' Char
'ϵ' = Char
'𝝐'
greekSerifBoldItalic' Char
'ϑ' = Char
'𝝑'
greekSerifBoldItalic' Char
'ϰ' = Char
'𝝒'
greekSerifBoldItalic' Char
'ϕ' = Char
'𝝓'
greekSerifBoldItalic' Char
'ϱ' = Char
'𝝔'
greekSerifBoldItalic' Char
'ϖ' = Char
'𝝕'
greekSerifBoldItalic' Char
c
  | Char
'Α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'Ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d38b Char
c
  | Char
'α' forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c forall a. Ord a => a -> a -> Bool
<= Char
'ω' = Int -> Char -> Char
_baseUpperLower Int
0x1d385 Char
c
  | Bool
otherwise = Char
c

-- | Convert the given character to a mathematical symbol with serifs, in
-- /bold/, and in /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifBoldItalic ::
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifBoldItalic :: Char -> Maybe Char
greekSerifBoldItalic = forall a b. (a -> Bool) -> (a -> b) -> a -> Maybe b
_withCondition Char -> Bool
isGreek Char -> Char
greekSerifBoldItalic'

-- | Convert the given character to a mathematical symbol with serifs, in /bold/
-- and in a /italics/ type. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifBold' ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, in bold and depending on the given 'ItalicType' in italics or not.
  Char
greekSerifBold' :: ItalicType -> Char -> Char
greekSerifBold' = forall a. a -> a -> ItalicType -> a
splitItalicType Char -> Char
greekSerifBoldNoItalic' Char -> Char
greekSerifBoldItalic'

-- | Convert the given character to a mathematical symbol with serifs, in /bold/
-- with the given /italics/ type wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifBold ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifBold :: ItalicType -> Char -> Maybe Char
greekSerifBold = forall a. a -> a -> ItalicType -> a
splitItalicType Char -> Maybe Char
greekSerifBoldNoItalic Char -> Maybe Char
greekSerifBoldItalic

-- | Convert the given character to a mathematical symbol with serifs, not in /bold/
-- and in a /italics/ type. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifNoBold' ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, not in bold and depending on the given 'ItalicType' in italics or not.
  Char
greekSerifNoBold' :: ItalicType -> Char -> Char
greekSerifNoBold' = forall a. a -> a -> ItalicType -> a
splitItalicType Char -> Char
greekSerifNoBoldNoItalic' Char -> Char
greekSerifNoBoldItalic'

-- | Convert the given character to a mathematical symbol with serifs, with no /bold/
-- and in the given /italics/ type wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifNoBold ::
  -- | The given 'ItalicType' to use.
  ItalicType ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifNoBold :: ItalicType -> Char -> Maybe Char
greekSerifNoBold = forall a. a -> a -> ItalicType -> a
splitItalicType Char -> Maybe Char
greekSerifNoBoldNoItalic Char -> Maybe Char
greekSerifNoBoldItalic

-- | Convert the given character to a mathematical symbol with serifs, with a
-- given /emphasis/ and in italics. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifItalic' ::
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, depending on the given 'Emphasis' in bold or not, and in italics.
  Char
greekSerifItalic' :: Emphasis -> Char -> Char
greekSerifItalic' = forall a. a -> a -> Emphasis -> a
splitEmphasis Char -> Char
greekSerifNoBoldItalic' Char -> Char
greekSerifBoldItalic'

-- | Convert the given character to a mathematical symbol with serifs, in the
-- given /emphasis/ and in /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifItalic ::
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifItalic :: Emphasis -> Char -> Maybe Char
greekSerifItalic = forall a. a -> a -> Emphasis -> a
splitEmphasis Char -> Maybe Char
greekSerifNoBoldItalic Char -> Maybe Char
greekSerifBoldItalic

-- | Convert the given character to a mathematical symbol with serifs, with a
-- given /emphasis/ and not in italics. This maps characters an equivalent serif symbol
-- for the characters in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@.
-- For characters outside the range, the behavior is unspecified.
greekSerifNoItalic' ::
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character that is formatted with serifs, depending on the given 'Emphasis' in bold or not, and not in italics.
  Char
greekSerifNoItalic' :: Emphasis -> Char -> Char
greekSerifNoItalic' = forall a. a -> a -> Emphasis -> a
splitEmphasis Char -> Char
greekSerifNoBoldNoItalic' Char -> Char
greekSerifBoldNoItalic'

-- | Convert the given character to a mathematical symbol with serifs, in the
-- given /emphasis/ and not in /italics/ wrapped in a 'Just'. If the character
-- is not in @ΑΒΓΔΕΖΗΘΙΚΛΜΝΞΟΠΡΣΤΥΦΧΨΩ∇ϴαβγδεζηθικλμνξοπρςστυφχψω∂ϵϑϰϕϱϖ@, 'Nothing' is returned.
greekSerifNoItalic ::
  -- | The given 'Emphasis' to use.
  Emphasis ->
  -- | The given character to convert.
  Char ->
  -- | The equivalent character wrapped in a 'Just' if in the valid range, 'Nothing' otherwise.
  Maybe Char
greekSerifNoItalic :: Emphasis -> Char -> Maybe Char
greekSerifNoItalic = forall a. a -> a -> Emphasis -> a
splitEmphasis Char -> Maybe Char
greekSerifNoBoldNoItalic Char -> Maybe Char
greekSerifBoldNoItalic