{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- Module      : Language.IPA
-- Copyright   : (c) 2021 Rory Tyler Hayford
--
-- License     : BSD-3-Clause
-- Maintainer  : rory.hayford@protonmail.com
-- Stability   : experimental
-- Portability : GHC
--
-- Working with IPA transcriptions
module Language.IPA
    ( module M
      -- * Converting to IPA representations
    , ReprIPA(..)
    ) where

import           Control.Exception  ( throw )

import           Data.Char          ( digitToInt )
import           Data.Text          ( Text )
import qualified Data.Text          as T

import           Language.IPA.Types as M
                 ( Backness(..)
                 , Consonant(..)
                 , Height(..)
                 , IPA(..)
                 , IPAException(..)
                 , Length(..)
                 , LevelTone(..)
                 , Manner(..)
                 , Phonation(..)
                 , Place(..)
                 , Roundedness(..)
                 , Segment(..)
                 , SegmentalFeature(..)
                 , Sibilance(..)
                 , Stress(..)
                 , SuprasegmentalFeature(..)
                 , Syllable(..)
                 , ToneContour(..)
                 , XSampa(..)
                 , mkIPA
                 , pattern ClickConsonant
                 , pattern EjectiveConsonant
                 , pattern ImplosiveConsonant
                 , pattern PulmonicConsonant
                 )

-- | Entities representable through IPA transcription
class ReprIPA a where
    -- | Produces an 'IPA' transcription given a valid 'Segment'; a result
    -- of @Nothing@ indicates either an unattested-yet-possible segment, or one
    -- considered impossible
    toIPA :: a -> Maybe IPA

    -- | Partial function for creating an 'IPA'. Useful if you are certain that
    -- the sound in question is representable
    toIPA' :: a -> IPA
    toIPA' (a -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA -> Just x :: IPA
x) = IPA
x
    toIPA' _                 = IPAException -> IPA
forall a e. Exception e => e -> a
throw (IPAException -> IPA) -> IPAException -> IPA
forall a b. (a -> b) -> a -> b
$ Text -> IPAException
InvalidIPA "Illegal IPA value"

    -- | Similar to 'toIPA'; produces an 'XSampa' transcription given a valid 'Segment'.
    toXSampa :: a -> Maybe XSampa

    -- | Partial function for creating an 'XSampa'. NB: Certain segments that have
    -- a defined 'IPA' representation have no 'XSampa' equivalent
    toXSampa' :: a -> XSampa
    toXSampa' (a -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa -> Just x :: XSampa
x) = XSampa
x
    toXSampa' _ = IPAException -> XSampa
forall a e. Exception e => e -> a
throw (IPAException -> XSampa) -> IPAException -> XSampa
forall a b. (a -> b) -> a -> b
$ Text -> IPAException
InvalidXSampa "Illegal IPA value"

instance Traversable t => ReprIPA (Syllable t) where
    toIPA :: Syllable t -> Maybe IPA
toIPA = \case
        Syllable ss :: t Segment
ss
            | t Segment -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null t Segment
ss -> Maybe IPA
forall a. Maybe a
Nothing
            | Bool
otherwise -> (IPA -> IPA -> IPA) -> t IPA -> IPA
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (t IPA -> IPA) -> Maybe (t IPA) -> Maybe IPA
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Segment -> Maybe IPA) -> t Segment -> Maybe (t IPA)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA t Segment
ss
        WithSuprasegmentalFeature feature :: SuprasegmentalFeature
feature s :: Syllable t
s ->
            Syllable t -> SuprasegmentalFeature -> Maybe IPA
forall (t :: * -> *).
Traversable t =>
Syllable t -> SuprasegmentalFeature -> Maybe IPA
withSuprasegmentalFeatureIPA Syllable t
s SuprasegmentalFeature
feature

    toXSampa :: Syllable t -> Maybe XSampa
toXSampa = \case
        Syllable ss :: t Segment
ss
            | t Segment -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null t Segment
ss -> Maybe XSampa
forall a. Maybe a
Nothing
            | Bool
otherwise -> (XSampa -> XSampa -> XSampa) -> t XSampa -> XSampa
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldr1 XSampa -> XSampa -> XSampa
forall a. Semigroup a => a -> a -> a
(<>) (t XSampa -> XSampa) -> Maybe (t XSampa) -> Maybe XSampa
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Segment -> Maybe XSampa) -> t Segment -> Maybe (t XSampa)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa t Segment
ss
        WithSuprasegmentalFeature feature :: SuprasegmentalFeature
feature s :: Syllable t
s ->
            Syllable t -> SuprasegmentalFeature -> Maybe XSampa
forall (t :: * -> *).
Traversable t =>
Syllable t -> SuprasegmentalFeature -> Maybe XSampa
withSuprasegmentalFeatureXSampa Syllable t
s SuprasegmentalFeature
feature

instance ReprIPA Segment where
    toIPA :: Segment -> Maybe IPA
toIPA = \case
        Zero -> Text -> Maybe IPA
mkJustIPA "∅"
        Consonant c :: Consonant
c -> Consonant -> Maybe IPA
consonantIPA Consonant
c
        v :: Segment
v@Vowel {} -> Segment -> Maybe IPA
vowelIPA Segment
v
        WithSegmentalFeature feature :: SegmentalFeature
feature s :: Segment
s -> Segment -> SegmentalFeature -> Maybe IPA
withSegmentalFeatureIPA Segment
s SegmentalFeature
feature

    toXSampa :: Segment -> Maybe XSampa
toXSampa = \case
        Zero -> Maybe XSampa
forall a. Maybe a
Nothing -- does not appear to have an X-SAMPA encoding
        v :: Segment
v@Vowel {} -> Segment -> Maybe XSampa
vowelXSampa Segment
v
        Consonant c :: Consonant
c -> Consonant -> Maybe XSampa
consonantXSampa Consonant
c
        WithSegmentalFeature feature :: SegmentalFeature
feature s :: Segment
s -> Segment -> SegmentalFeature -> Maybe XSampa
withSegmentalFeatureXSampa Segment
s SegmentalFeature
feature

mkJustIPA :: Text -> Maybe IPA
mkJustIPA :: Text -> Maybe IPA
mkJustIPA = IPA -> Maybe IPA
forall a. a -> Maybe a
Just (IPA -> Maybe IPA) -> (Text -> IPA) -> Text -> Maybe IPA
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IPA
mkIPA

mkIPAOp :: ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp :: (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp f :: b -> Maybe IPA
f x :: a
x y :: b
y = IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (IPA -> IPA -> IPA) -> Maybe IPA -> Maybe (IPA -> IPA)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA a
x Maybe (IPA -> IPA) -> Maybe IPA -> Maybe IPA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe IPA
f b
y

withSuprasegmentalFeatureIPA
    :: Traversable t => Syllable t -> SuprasegmentalFeature -> Maybe IPA
withSuprasegmentalFeatureIPA :: Syllable t -> SuprasegmentalFeature -> Maybe IPA
withSuprasegmentalFeatureIPA s :: Syllable t
s = \case
    LevelLexicalTone tone :: LevelTone
tone -> (LevelTone -> Maybe IPA) -> Syllable t -> LevelTone -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp LevelTone -> Maybe IPA
ipaTone Syllable t
s LevelTone
tone
      where
        ipaTone :: LevelTone -> Maybe IPA
ipaTone = \case
            ExtraHighTone -> Text -> Maybe IPA
mkJustIPA "˥"
            HighTone      -> Text -> Maybe IPA
mkJustIPA "˦"
            MidTone       -> Text -> Maybe IPA
mkJustIPA "˧"
            LowTone       -> Text -> Maybe IPA
mkJustIPA "˨"
            ExtraLowTone  -> Text -> Maybe IPA
mkJustIPA "˩"
            -- Down-step and up-step are represented with
            -- diacritics, not tone characters
            _             -> Maybe IPA
forall a. Maybe a
Nothing

    LevelLexicalToneDiacritic tone :: LevelTone
tone -> (LevelTone -> Maybe IPA) -> Syllable t -> LevelTone -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp LevelTone -> Maybe IPA
ipaTone Syllable t
s LevelTone
tone
      where
        ipaTone :: LevelTone -> Maybe IPA
ipaTone = \case
            ExtraHighTone -> Text -> Maybe IPA
mkJustIPA "\x030b" -- ◌̋
            HighTone      -> Text -> Maybe IPA
mkJustIPA "\x0341" -- ◌́
            MidTone       -> Text -> Maybe IPA
mkJustIPA "\x0304" -- ◌̄
            LowTone       -> Text -> Maybe IPA
mkJustIPA "\x0340" -- ◌̀
            ExtraLowTone  -> Text -> Maybe IPA
mkJustIPA "\x030f" -- ◌̏
            DownStep      -> Text -> Maybe IPA
mkJustIPA "ꜜ"
            UpStep        -> Text -> Maybe IPA
mkJustIPA "ꜛ"

    LexicalToneContour tone :: ToneContour
tone -> (ToneContour -> Maybe IPA)
-> Syllable t -> ToneContour -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp ToneContour -> Maybe IPA
ipaToneContour Syllable t
s ToneContour
tone
      where
        ipaToneContour :: ToneContour -> Maybe IPA
ipaToneContour = \case
            Rising        -> Text -> Maybe IPA
mkJustIPA "˩˥"
            Falling       -> Text -> Maybe IPA
mkJustIPA "˥˩"
            HighRising    -> Text -> Maybe IPA
mkJustIPA "˧˥"
            LowRising     -> Text -> Maybe IPA
mkJustIPA "˩˧"
            HighFalling   -> Text -> Maybe IPA
mkJustIPA "˥˧"
            LowFalling    -> Text -> Maybe IPA
mkJustIPA "˧˩"
            RisingFalling -> Text -> Maybe IPA
mkJustIPA "˧˦˨"
            FallingRising -> Text -> Maybe IPA
mkJustIPA "˧˨˦"
            GlobalRise    -> Text -> Maybe IPA
mkJustIPA "↗"
            GlobalFall    -> Text -> Maybe IPA
mkJustIPA "↙"

    LexicalToneContourDiacritic tone :: ToneContour
tone -> (ToneContour -> Maybe IPA)
-> Syllable t -> ToneContour -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp ToneContour -> Maybe IPA
ipaToneContour Syllable t
s ToneContour
tone
      where
        ipaToneContour :: ToneContour -> Maybe IPA
ipaToneContour = \case
            Rising        -> Text -> Maybe IPA
mkJustIPA "\x0302" -- ◌̂
            Falling       -> Text -> Maybe IPA
mkJustIPA "\x030c" -- ◌̌
            HighRising    -> Text -> Maybe IPA
mkJustIPA "\x1dc9" -- ◌᷉
            LowRising     -> Text -> Maybe IPA
mkJustIPA "\x1dc5" -- ◌᷅
            HighFalling   -> Text -> Maybe IPA
mkJustIPA "\x1dc7" -- ◌᷇
            LowFalling    -> Text -> Maybe IPA
mkJustIPA "\x1dc6" -- ◌᷆
            RisingFalling -> Text -> Maybe IPA
mkJustIPA "\x1dc8" -- ◌᷈
            FallingRising -> Text -> Maybe IPA
mkJustIPA "\x1dc9" -- ◌᷉
            -- 'GlobalRise' and 'GlobalFall' don't have
            -- diacritic representations
            _             -> Maybe IPA
forall a. Maybe a
Nothing

    Stress stress :: Stress
stress -> (Stress -> Maybe IPA) -> Syllable t -> Stress -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp Stress -> Maybe IPA
ipaStress Syllable t
s Stress
stress
      where
        ipaStress :: Stress -> Maybe IPA
ipaStress Primary   = Text -> Maybe IPA
mkJustIPA "ˈ"
        ipaStress Secondary = Text -> Maybe IPA
mkJustIPA "ˌ"

    Break -> IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (IPA -> IPA -> IPA) -> Maybe IPA -> Maybe (IPA -> IPA)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Syllable t -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA Syllable t
s Maybe (IPA -> IPA) -> Maybe IPA -> Maybe IPA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe IPA
mkJustIPA "."

    Linking -> IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (IPA -> IPA -> IPA) -> Maybe IPA -> Maybe (IPA -> IPA)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Syllable t -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA Syllable t
s Maybe (IPA -> IPA) -> Maybe IPA -> Maybe IPA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe IPA
mkJustIPA "‿"

withSegmentalFeatureIPA :: Segment -> SegmentalFeature -> Maybe IPA
withSegmentalFeatureIPA :: Segment -> SegmentalFeature -> Maybe IPA
withSegmentalFeatureIPA s :: Segment
s = \case
    Voicing v :: Phonation
v -> (Phonation -> Maybe IPA) -> Segment -> Phonation -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp Phonation -> Maybe IPA
ipaVoicing Segment
s Phonation
v
      where
        ipaVoicing :: Phonation -> Maybe IPA
ipaVoicing = \case
            Voiceless -> Text -> Maybe IPA
mkJustIPA "\x030a" -- ◌̊
            Voiced    -> Text -> Maybe IPA
mkJustIPA "\x030c" -- ◌̌
    Length l :: Length
l -> (Length -> Maybe IPA) -> Segment -> Length -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp Length -> Maybe IPA
ipaLength Segment
s Length
l
      where
        ipaLength :: Length -> Maybe IPA
ipaLength = \case
            OverLong   -> Text -> Maybe IPA
mkJustIPA "ːː"
            HalfLong   -> Text -> Maybe IPA
mkJustIPA "ˑ"
            Long       -> Text -> Maybe IPA
mkJustIPA "ː"
            Short      -> Text -> Maybe IPA
mkJustIPA Text
forall a. Monoid a => a
mempty
            ExtraShort -> Text -> Maybe IPA
mkJustIPA "\x0306" -- ◌ ̆
    SecondaryArticulation sa :: Segment
sa -> (Segment -> Maybe IPA) -> Segment -> Segment -> Maybe IPA
forall a b. ReprIPA a => (b -> Maybe IPA) -> a -> b -> Maybe IPA
mkIPAOp Segment -> Maybe IPA
secondaryArticulationIPA Segment
s Segment
sa
    SuperScriptNumeric ns :: Int
ns -> IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (IPA -> IPA -> IPA) -> Maybe IPA -> Maybe (IPA -> IPA)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA Segment
s Maybe (IPA -> IPA) -> Maybe IPA -> Maybe IPA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe IPA
mkJustIPA Text
digits
      where
        digits :: Text
digits = [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> [String] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Int -> String
code (Int -> String) -> (Char -> Int) -> Char -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
digitToInt (Char -> String) -> String -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> String
forall a. Show a => a -> String
show Int
ns)

        code :: Int -> String
code   = \case
            0 -> "\x2070"
            1 -> "\x00b9"
            2 -> "\x00b2"
            3 -> "\x00b3"
            4 -> "\x2074"
            5 -> "\x2075"
            6 -> "\x2076"
            7 -> "\x2077"
            8 -> "\x2078"
            9 -> "\x2079"
            _ -> String
forall a. Monoid a => a
mempty

    feature :: SegmentalFeature
feature -> IPA -> IPA -> IPA
forall a. Semigroup a => a -> a -> a
(<>) (IPA -> IPA -> IPA) -> Maybe IPA -> Maybe (IPA -> IPA)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA Segment
s Maybe (IPA -> IPA) -> Maybe IPA -> Maybe IPA
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> case SegmentalFeature
feature of
        Aspirated           -> Text -> Maybe IPA
mkJustIPA "\x02b0" -- ◌ʰ
        MoreRounded         -> Text -> Maybe IPA
mkJustIPA "\x0339" -- ◌̹
        LessRounded         -> Text -> Maybe IPA
mkJustIPA "\x031c" -- ◌̜
        Advanced            -> Text -> Maybe IPA
mkJustIPA "\x031f" -- ◌̟
        Retracted           -> Text -> Maybe IPA
mkJustIPA "\x0320" -- ◌̠
        Centralized         -> Text -> Maybe IPA
mkJustIPA "\x0308" -- ◌̈
        MidCentralized      -> Text -> Maybe IPA
mkJustIPA "\x033d" -- ◌̽
        Compressed          -> Text -> Maybe IPA
mkJustIPA "\x1d5d" -- ◌ᵝ
        Syllabic            -> Text -> Maybe IPA
mkJustIPA "\x0329" -- ◌̩
        NonSyllabic         -> Text -> Maybe IPA
mkJustIPA "\x032f" -- ◌̯
        Rhotacized          -> Text -> Maybe IPA
mkJustIPA "\x02de" -- ◌˞
        BreathyVoice        -> Text -> Maybe IPA
mkJustIPA "\x0324" -- ◌̤
        CreakyVoice         -> Text -> Maybe IPA
mkJustIPA "\x0330" -- ◌̰
        LinguoLabialized    -> Text -> Maybe IPA
mkJustIPA "\x033c" -- ◌̼
        Labialized          -> Text -> Maybe IPA
mkJustIPA "\x02b7" -- ◌ʷ
        Palatalized         -> Text -> Maybe IPA
mkJustIPA "\x02b2" -- ◌ʲ
        Velarized           -> Text -> Maybe IPA
mkJustIPA "\x02e0" -- ◌ˠ
        Pharyngealized      -> Text -> Maybe IPA
mkJustIPA "\x02e4" -- ◌ˤ
        Raised              -> Text -> Maybe IPA
mkJustIPA "\x031d" -- ◌̝
        Lowered             -> Text -> Maybe IPA
mkJustIPA "\x031e" -- ◌̞
        AdvancedTongueRoot  -> Text -> Maybe IPA
mkJustIPA "\x0318" -- ◌̘
        RetractedTongueRoot -> Text -> Maybe IPA
mkJustIPA "\x0319" -- ◌̙
        Dentalized          -> Text -> Maybe IPA
mkJustIPA "\x032a" -- ◌̪
        Apical              -> Text -> Maybe IPA
mkJustIPA "\x033a" -- ◌̺
        Laminal             -> Text -> Maybe IPA
mkJustIPA "\x033b" -- ◌̻
        Nasalized           -> Text -> Maybe IPA
mkJustIPA "\x0303" -- ◌̃
        NasalRelease        -> Text -> Maybe IPA
mkJustIPA "\x207f" -- ◌ⁿ
        LateralRelease      -> Text -> Maybe IPA
mkJustIPA "\x02e1" -- ◌ˡ
        NoAudibleRelease    -> Text -> Maybe IPA
mkJustIPA "\x031a" -- ◌̚
        _                   -> Text -> Maybe IPA
mkJustIPA "" --

consonantIPA :: Consonant -> Maybe IPA
consonantIPA :: Consonant -> Maybe IPA
consonantIPA = \case
    -- Pulmonic consonants
    -- Bilabials
    Pulmonic Voiceless Bilabial Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Bilabial Manner
Nasal)
    Pulmonic Voiced Bilabial Nasal -> Text -> Maybe IPA
mkJustIPA "m"
    Pulmonic Voiced Bilabial Plosive -> Text -> Maybe IPA
mkJustIPA "b"
    Pulmonic Voiceless Bilabial Plosive -> Text -> Maybe IPA
mkJustIPA "p"
    Pulmonic Voiceless Bilabial (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "p͡ɸ"
    Pulmonic Voiced Bilabial (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "b͡β"
    Pulmonic Voiceless Bilabial (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɸ"
    Pulmonic Voiced Bilabial (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "β"
    Pulmonic Voiced Bilabial Flap -> Text -> Maybe IPA
mkJustIPA "ⱱ̟"
    Pulmonic Voiceless Bilabial Trill -> Text -> Maybe IPA
mkJustIPA "ʙ̥"
    Pulmonic Voiced Bilabial Trill -> Text -> Maybe IPA
mkJustIPA "ʙ"

    -- Labio-dentals
    Pulmonic Voiced LabioDental Nasal -> Text -> Maybe IPA
mkJustIPA "ɱ"
    Pulmonic Voiceless LabioDental Plosive -> Text -> Maybe IPA
mkJustIPA "p̪"
    Pulmonic Voiced LabioDental Plosive -> Text -> Maybe IPA
mkJustIPA "b̪"
    Pulmonic Voiceless LabioDental (Affricate NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "p̪͡f"
    Pulmonic Voiced LabioDental (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "b̪͡v"
    Pulmonic Voiceless LabioDental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "f"
    Pulmonic Voiced LabioDental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "v"
    Pulmonic Voiced LabioDental Approximant -> Text -> Maybe IPA
mkJustIPA "ʋ"
    Pulmonic Voiced LabioDental Flap -> Text -> Maybe IPA
mkJustIPA "ⱱ"

    -- Linguo-labials
    Pulmonic Voiced LinguoLabial Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Nasal)
    Pulmonic Voiceless LinguoLabial Plosive -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiceless Place
Alveolar Manner
Plosive)
    Pulmonic Voiced LinguoLabial Plosive -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Plosive)
    Pulmonic Voiceless LinguoLabial (Fricative NonSibilant) -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiceless
                                                  Place
Alveolar
                                                  (Sibilance -> Manner
Fricative Sibilance
NonSibilant))

    Pulmonic Voiced LinguoLabial (Fricative NonSibilant) -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced
                                                  Place
Alveolar
                                                  (Sibilance -> Manner
Fricative Sibilance
NonSibilant))
    Pulmonic Voiced LinguoLabial Flap -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
LinguoLabialized
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Flap)

    -- Dentals
    Pulmonic Voiceless Dental (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "t̼͡θ"
    Pulmonic Voiced Dental (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "d̼͡ð"
    Pulmonic Voiceless Dental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "θ"
    Pulmonic Voiced Dental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ð"

    -- Alveolars
    Pulmonic Voiceless Alveolar Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Nasal)
    Pulmonic Voiced Alveolar Nasal -> Text -> Maybe IPA
mkJustIPA "n"
    Pulmonic Voiceless Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "t"
    Pulmonic Voiced Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "d"
    Pulmonic Voiceless Alveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡s"
    Pulmonic Voiced Alveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "d͡z"
    Pulmonic Voiceless Alveolar (Affricate NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "t͡ɹ̝̊"
    Pulmonic Voiced Alveolar (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "d͡ɹ̝"
    Pulmonic Voiceless Alveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "s"
    Pulmonic Voiced Alveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "z"
    Pulmonic Voiced Alveolar Approximant -> Text -> Maybe IPA
mkJustIPA "ɹ"
    Pulmonic Voiceless Alveolar Flap -> Text -> Maybe IPA
mkJustIPA "ɾ̥"
    Pulmonic Voiced Alveolar Flap -> Text -> Maybe IPA
mkJustIPA "ɾ"
    Pulmonic Voiceless Alveolar Trill -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Trill)
    Pulmonic Voiced Alveolar Trill -> Text -> Maybe IPA
mkJustIPA "r"
    Pulmonic Voiceless Alveolar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "tɬ"
    Pulmonic Voiced Alveolar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "dɮ"
    Pulmonic Voiceless Alveolar LateralFricative -> Text -> Maybe IPA
mkJustIPA "ɬ"
    Pulmonic Voiced Alveolar LateralFricative -> Text -> Maybe IPA
mkJustIPA "ɮ"
    Pulmonic Voiced Alveolar LateralApproximant -> Text -> Maybe IPA
mkJustIPA "l"
    Pulmonic Voiceless Alveolar LateralFlap -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
LateralFlap)
    Pulmonic Voiced Alveolar LateralFlap -> Text -> Maybe IPA
mkJustIPA "ɺ"

    -- Post-alveolars
    Pulmonic Voiceless PostAlveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡ʃ"
    Pulmonic Voiced PostAlveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "d͡ʒ"
    Pulmonic Voiceless PostAlveolar (Affricate NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "tɹ̠̊˔"
    Pulmonic Voiced PostAlveolar (Affricate NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "d͡ɹ̠˔"
    Pulmonic Voiceless PostAlveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʃ"
    Pulmonic Voiced PostAlveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʒ"
    Pulmonic Voiceless PostAlveolar (Fricative NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "ɹ̠̊˔"
    Pulmonic Voiced PostAlveolar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɹ̠˔"

    -- Retroflexes
    Pulmonic Voiceless Retroflex Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Retroflex Manner
Nasal)
    Pulmonic Voiced Retroflex Nasal -> Text -> Maybe IPA
mkJustIPA "ɳ"
    Pulmonic Voiceless Retroflex Plosive -> Text -> Maybe IPA
mkJustIPA "ʈ"
    Pulmonic Voiced Retroflex Plosive -> Text -> Maybe IPA
mkJustIPA "ɖ"
    Pulmonic Voiceless Retroflex (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʈ͡ʂ"
    Pulmonic Voiced Retroflex (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "ɖ͡ʐ"
    Pulmonic Voiceless Retroflex (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʂ"
    Pulmonic Voiced Retroflex (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʐ"
    Pulmonic Voiced Retroflex (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɻ˔"
    Pulmonic Voiced Retroflex Approximant -> Text -> Maybe IPA
mkJustIPA "ɻ"
    Pulmonic Voiceless Retroflex Flap -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Retroflex Manner
Flap)
    Pulmonic Voiced Retroflex Flap -> Text -> Maybe IPA
mkJustIPA "ɽ"
    Pulmonic Voiceless Retroflex Trill -> Text -> Maybe IPA
mkJustIPA "ɽ̊r̥"
    Pulmonic Voiced Retroflex Trill -> Text -> Maybe IPA
mkJustIPA "ɽr"
    Pulmonic Voiceless Retroflex LateralAffricate -> Text -> Maybe IPA
mkJustIPA "ʈɭ̊˔"
    Pulmonic Voiced Retroflex LateralAffricate -> Text -> Maybe IPA
mkJustIPA "ɖɭ˔"
    Pulmonic Voiceless Retroflex LateralFricative -> Text -> Maybe IPA
mkJustIPA "ɭ̊˔"
    Pulmonic Voiced Retroflex LateralFricative -> Text -> Maybe IPA
mkJustIPA "ɭ˔"
    Pulmonic Voiced Retroflex LateralApproximant -> Text -> Maybe IPA
mkJustIPA "ɭ"
    Pulmonic Voiceless Retroflex LateralFlap -> Text -> Maybe IPA
mkJustIPA "ɭ̥̆"
    Pulmonic Voiced Retroflex LateralFlap -> Text -> Maybe IPA
mkJustIPA "ɭ̆"

    -- Palatals
    Pulmonic Voiceless Palatal Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Palatal Manner
Nasal)
    Pulmonic Voiced Palatal Nasal -> Text -> Maybe IPA
mkJustIPA "ɲ"
    Pulmonic Voiceless Palatal Plosive -> Text -> Maybe IPA
mkJustIPA "c"
    Pulmonic Voiced Palatal Plosive -> Text -> Maybe IPA
mkJustIPA "ɟ"
    Pulmonic Voiceless Palatal (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡ɕ"
    Pulmonic Voiced Palatal (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "d͡ʑ"
    Pulmonic Voiceless Palatal (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "c͡ç"
    Pulmonic Voiced Palatal (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɟ͡ʝ"
    Pulmonic Voiceless Palatal (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ɕ"
    Pulmonic Voiced Palatal (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʑ"
    Pulmonic Voiceless Palatal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ç"
    Pulmonic Voiced Palatal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ʝ"
    Pulmonic Voiced Palatal Approximant -> Text -> Maybe IPA
mkJustIPA "j"
    Pulmonic Voiceless Palatal LateralAffricate -> Text -> Maybe IPA
mkJustIPA "cʎ̝̊"
    Pulmonic Voiced Palatal LateralAffricate -> Text -> Maybe IPA
mkJustIPA "ɟʎ̝"
    Pulmonic Voiceless Palatal LateralFricative -> Text -> Maybe IPA
mkJustIPA "ʎ̝̊"
    Pulmonic Voiced Palatal LateralFricative -> Text -> Maybe IPA
mkJustIPA "ʎ̝"
    Pulmonic Voiced Palatal LateralApproximant -> Text -> Maybe IPA
mkJustIPA "ʎ"
    Pulmonic Voiced Palatal LateralFlap -> Text -> Maybe IPA
mkJustIPA "ʎ̆"

    -- Velars
    Pulmonic Voiceless Velar Nasal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Velar Manner
Nasal)
    Pulmonic Voiced Velar Nasal -> Text -> Maybe IPA
mkJustIPA "ŋ"
    Pulmonic Voiceless Velar Plosive -> Text -> Maybe IPA
mkJustIPA "k"
    Pulmonic Voiced Velar Plosive -> Text -> Maybe IPA
mkJustIPA "g"
    Pulmonic Voiceless Velar (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "k͡x"
    Pulmonic Voiced Velar (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "g͡ɣ"
    Pulmonic Voiceless Velar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "x"
    Pulmonic Voiced Velar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɣ"
    Pulmonic Voiced Velar Approximant -> Text -> Maybe IPA
mkJustIPA "ɰ"
    Pulmonic Voiceless Velar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "kʟ̝̊"
    Pulmonic Voiced Velar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "ɡʟ̝"
    Pulmonic Voiceless Velar LateralFricative -> Text -> Maybe IPA
mkJustIPA "ʟ̝̊"
    Pulmonic Voiced Velar LateralFricative -> Text -> Maybe IPA
mkJustIPA "ʟ̝"
    Pulmonic Voiced Velar LateralApproximant -> Text -> Maybe IPA
mkJustIPA "ʟ"
    Pulmonic Voiced Velar LateralFlap -> Text -> Maybe IPA
mkJustIPA "ʟ̆"

    -- Uvulars
    Pulmonic Voiced Uvular Nasal -> Text -> Maybe IPA
mkJustIPA "ɴ"
    Pulmonic Voiceless Uvular Plosive -> Text -> Maybe IPA
mkJustIPA "q"
    Pulmonic Voiced Uvular Plosive -> Text -> Maybe IPA
mkJustIPA "ɢ"
    Pulmonic Voiceless Uvular (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "q͡χ"
    Pulmonic Voiced Uvular (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɢ͡ʁ"
    Pulmonic Voiceless Uvular (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "χ"
    Pulmonic Voiced Uvular (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ʁ"
    Pulmonic Voiced Uvular Flap -> Text -> Maybe IPA
mkJustIPA "ɢ̆"
    Pulmonic Voiceless Uvular Trill -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Uvular Manner
Trill)
    Pulmonic Voiced Uvular Trill -> Text -> Maybe IPA
mkJustIPA "ʀ"
    Pulmonic Voiced Uvular LateralApproximant -> Text -> Maybe IPA
mkJustIPA "ʟ̠"

    -- Pharyngeals
    Pulmonic Voiceless Pharyngeal Plosive -> Text -> Maybe IPA
mkJustIPA "ʡ"
    Pulmonic Voiced Pharyngeal (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ʡ͡ʢ"
    Pulmonic Voiceless Pharyngeal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ħ"
    Pulmonic Voiced Pharyngeal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ʕ"
    Pulmonic Voiced Pharyngeal Flap -> Text -> Maybe IPA
mkJustIPA "̆ʡ̆"
    Pulmonic Voiceless Pharyngeal Trill -> Text -> Maybe IPA
mkJustIPA "ʜ"
    Pulmonic Voiced Pharyngeal Trill -> Text -> Maybe IPA
mkJustIPA "ʢ"

    -- Glottals
    Pulmonic Voiceless Glottal Plosive -> Text -> Maybe IPA
mkJustIPA "ʔ"
    Pulmonic Voiceless Glottal (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ʔ͡h"
    Pulmonic Voiceless Glottal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "h"
    Pulmonic Voiced Glottal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɦ"
    Pulmonic Voiced Glottal Approximant -> Text -> Maybe IPA
mkJustIPA "̆̆ʔ̞"

    -- Ejectives
    -- Bilabials
    Ejective Bilabial Plosive -> Text -> Maybe IPA
mkJustIPA "pʼ"
    Ejective Bilabial (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "ɸʼ"

    -- Labio-dentals
    Ejective LabioDental (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "p̪͡fʼ"
    Ejective LabioDental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "fʼ"

    -- Dentals
    Ejective Dental Plosive -> Text -> Maybe IPA
mkJustIPA "t̪ʼ"
    Ejective Dental (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "t̪͡θʼ"
    Ejective Dental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "θʼ"

    -- Alveolars
    Ejective Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "tʼ"
    Ejective Alveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡sʼ"
    Ejective Alveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "sʼ"
    Ejective Alveolar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "t͡ɬʼ"
    Ejective Alveolar LateralFricative -> Text -> Maybe IPA
mkJustIPA "ɬʼ"

    -- Post-alveolars
    Ejective PostAlveolar (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡ʃʼ"
    Ejective PostAlveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʃʼ"

    -- Retroflexes
    Ejective Retroflex Plosive -> Text -> Maybe IPA
mkJustIPA "ʈʼ"
    Ejective Retroflex (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʈ͡ʂʼ"
    Ejective Retroflex (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ʂʼ"

    -- Palatals
    Ejective Palatal Plosive -> Text -> Maybe IPA
mkJustIPA "cʼ"
    Ejective Palatal (Affricate Sibilant) -> Text -> Maybe IPA
mkJustIPA "t͡ɕʼ"
    Ejective Palatal (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "ɕʼ"
    Ejective Palatal LateralAffricate -> Text -> Maybe IPA
mkJustIPA "cʎ̝̊ʼ"

    -- Velars
    Ejective Velar Plosive -> Text -> Maybe IPA
mkJustIPA "kʼ"
    Ejective Velar (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "k͡xʼ"
    Ejective Velar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "xʼ"
    Ejective Velar LateralAffricate -> Text -> Maybe IPA
mkJustIPA "kʟ̝̊ʼ"

    -- Uvulars
    Ejective Uvular Plosive -> Text -> Maybe IPA
mkJustIPA "qʼ"
    Ejective Uvular (Affricate NonSibilant) -> Text -> Maybe IPA
mkJustIPA "q͡χʼ"
    Ejective Uvular (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "χʼ"

    -- Pharyngeals
    Ejective Pharyngeal Plosive -> Text -> Maybe IPA
mkJustIPA "ʡʼ"

    -- Implosives
    Implosive Voiceless Bilabial -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Alveolar)
    Implosive Voiced Bilabial -> Text -> Maybe IPA
mkJustIPA "ɓ"
    Implosive Voiceless Dental -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Dental)
    Implosive Voiced Dental -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Dentalized (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Alveolar)
    Implosive Voiced Alveolar -> Text -> Maybe IPA
mkJustIPA "ɗ"
    Implosive Voiceless Alveolar -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Alveolar)
    Implosive Voiced Retroflex -> Text -> Maybe IPA
mkJustIPA "ᶑ"
    Implosive Voiceless Retroflex -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Retroflex)
    Implosive Voiceless Palatal -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Palatal)
    Implosive Voiced Palatal -> Text -> Maybe IPA
mkJustIPA "ʄ"
    Implosive Voiceless Velar -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Velar)
    Implosive Voiced Velar -> Text -> Maybe IPA
mkJustIPA "ɠ"
    Implosive Voiceless Uvular -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Uvular)
    Implosive Voiced Uvular -> Text -> Maybe IPA
mkJustIPA "ʛ"

    -- Clicks
    Click Bilabial -> Text -> Maybe IPA
mkJustIPA "ʘ"
    Click Dental -> Text -> Maybe IPA
mkJustIPA "ǀ"
    Click Alveolar -> Text -> Maybe IPA
mkJustIPA "ǃ"
    Click PostAlveolar -> Text -> Maybe IPA
mkJustIPA "ǁ" -- lateral click
    Click Palatal -> Text -> Maybe IPA
mkJustIPA "ǂ"

    -- Double articulation
    DoublyArticulated Voiced Bilabial Alveolar Nasal -> Text -> Maybe IPA
mkJustIPA "n͡m"
    DoublyArticulated Voiceless Bilabial Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "t͡p"
    DoublyArticulated Voiced Bilabial Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "d͡b"
    DoublyArticulated Voiced Bilabial Velar Nasal -> Text -> Maybe IPA
mkJustIPA "ŋ͡m"
    DoublyArticulated Voiceless Bilabial Velar Plosive -> Text -> Maybe IPA
mkJustIPA "k͡p"
    DoublyArticulated Voiced Bilabial Velar Plosive -> Text -> Maybe IPA
mkJustIPA "g͡b"
    DoublyArticulated Voiceless Uvular Pharyngeal Plosive -> Text -> Maybe IPA
mkJustIPA "q͡ʡ"
    DoublyArticulated Voiceless Bilabial Palatal (Fricative NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "ɥ̊"
    DoublyArticulated Voiced Bilabial Palatal Approximant -> Text -> Maybe IPA
mkJustIPA "ɥ"
    DoublyArticulated Voiceless Bilabial Velar (Fricative NonSibilant) ->
        Text -> Maybe IPA
mkJustIPA "ʍ"
    DoublyArticulated Voiced Bilabial Velar Approximant -> Text -> Maybe IPA
mkJustIPA "w"
    DoublyArticulated Voiced Alveolar Velar LateralApproximant ->
        Text -> Maybe IPA
mkJustIPA "ɫ"
    -- The sj-sound in Swedish phonology; actual realization is contested
    -- and appears to vary between dialects
    DoublyArticulated Voiceless PostAlveolar Velar (Fricative Sibilant) ->
        Text -> Maybe IPA
mkJustIPA "ɧ"
    DoublyArticulated Voiceless LabioDental Velar (Fricative Sibilant) ->
        Text -> Maybe IPA
mkJustIPA "ɧ"

    _ -> Maybe IPA
forall a. Maybe a
Nothing

vowelIPA :: Segment -> Maybe IPA
vowelIPA :: Segment -> Maybe IPA
vowelIPA = \case
    Vowel Close Front Unrounded -> Text -> Maybe IPA
mkJustIPA "i"
    Vowel Close Front Rounded -> Text -> Maybe IPA
mkJustIPA "y"
    Vowel Close Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ɨ"
    Vowel Close Central Rounded -> Text -> Maybe IPA
mkJustIPA "ʉ"
    Vowel Close Back Unrounded -> Text -> Maybe IPA
mkJustIPA "ɯ"
    Vowel Close Back Rounded -> Text -> Maybe IPA
mkJustIPA "u"
    Vowel NearClose Front Unrounded -> Text -> Maybe IPA
mkJustIPA "ɪ"
    Vowel NearClose Front Rounded -> Text -> Maybe IPA
mkJustIPA "ʏ"
    Vowel NearClose Back Rounded -> Text -> Maybe IPA
mkJustIPA "ʊ"
    Vowel CloseMid Front Unrounded -> Text -> Maybe IPA
mkJustIPA "e"
    Vowel CloseMid Front Rounded -> Text -> Maybe IPA
mkJustIPA "ø"
    Vowel CloseMid Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ɘ"
    Vowel CloseMid Central Rounded -> Text -> Maybe IPA
mkJustIPA "ɵ"
    Vowel CloseMid Back Unrounded -> Text -> Maybe IPA
mkJustIPA "ɤ"
    Vowel CloseMid Back Rounded -> Text -> Maybe IPA
mkJustIPA "o"
    Vowel Mid Front Unrounded -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Front Roundedness
Unrounded)
    Vowel Mid Front Rounded -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Front Roundedness
Rounded)
    Vowel Mid Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ə"
    Vowel Mid Back Unrounded -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Back Roundedness
Unrounded)
    Vowel Mid Back Rounded -> Segment -> Maybe IPA
forall a. ReprIPA a => a -> Maybe IPA
toIPA
        (Segment -> Maybe IPA) -> Segment -> Maybe IPA
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Back Roundedness
Rounded)
    Vowel OpenMid Front Unrounded -> Text -> Maybe IPA
mkJustIPA "ɛ"
    Vowel OpenMid Front Rounded -> Text -> Maybe IPA
mkJustIPA "œ"
    Vowel OpenMid Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ɜ"
    Vowel OpenMid Central Rounded -> Text -> Maybe IPA
mkJustIPA "ɞ"
    Vowel OpenMid Back Unrounded -> Text -> Maybe IPA
mkJustIPA "ʌ"
    Vowel OpenMid Back Rounded -> Text -> Maybe IPA
mkJustIPA "ɔ"
    Vowel NearOpen Front Unrounded -> Text -> Maybe IPA
mkJustIPA "æ"
    Vowel NearOpen Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ɐ"
    Vowel Open Front Unrounded -> Text -> Maybe IPA
mkJustIPA "a"
    Vowel Open Front Rounded -> Text -> Maybe IPA
mkJustIPA "ɶ"
    Vowel Open Central Unrounded -> Text -> Maybe IPA
mkJustIPA "ä"
    Vowel Open Back Unrounded -> Text -> Maybe IPA
mkJustIPA "ɑ"
    Vowel Open Back Rounded -> Text -> Maybe IPA
mkJustIPA "ɒ"
    _ -> Maybe IPA
forall a. Maybe a
Nothing

secondaryArticulationIPA :: Segment -> Maybe IPA
secondaryArticulationIPA :: Segment -> Maybe IPA
secondaryArticulationIPA = \case
    Consonant c :: Consonant
c -> case Consonant
c of
        Pulmonic Voiced Bilabial Nasal -> Text -> Maybe IPA
mkJustIPA "\x1d50"
        Pulmonic Voiced LabioDental Nasal -> Text -> Maybe IPA
mkJustIPA "\x1dac"
        Pulmonic Voiced Alveolar Nasal -> Text -> Maybe IPA
mkJustIPA "\x207f"
        Pulmonic Voiced Retroflex Nasal -> Text -> Maybe IPA
mkJustIPA "\x1daf"
        Pulmonic Voiced Palatal Nasal -> Text -> Maybe IPA
mkJustIPA "\x1dae"
        Pulmonic Voiced Velar Nasal -> Text -> Maybe IPA
mkJustIPA "\x1d51"
        Pulmonic Voiced Uvular Nasal -> Text -> Maybe IPA
mkJustIPA "\x1db0"

        Pulmonic Voiced Bilabial Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d56"
        Pulmonic Voiceless Bilabial Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d47"
        Pulmonic Voiceless Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d57"
        Pulmonic Voiced Alveolar Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d48"
        Pulmonic Voiceless Palatal Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d9c"
        Pulmonic Voiced Palatal Plosive -> Text -> Maybe IPA
mkJustIPA "\x1da1"
        Pulmonic Voiceless Velar Plosive -> Text -> Maybe IPA
mkJustIPA "\x1d4f"
        Pulmonic Voiced Velar Plosive -> Text -> Maybe IPA
mkJustIPA "\x1da2"
        Pulmonic Voiceless Glottal Plosive -> Text -> Maybe IPA
mkJustIPA "\x02c0"

        Pulmonic Voiced Bilabial (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x1db2"
        Pulmonic Voiceless Bilabial (Fricative NonSibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x1d5d"
        Pulmonic Voiced LabioDental (Fricative NonSibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x1da0"
        Pulmonic Voiceless LabioDental (Fricative NonSibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x1d5b"
        Pulmonic Voiceless Dental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x1dbf"
        Pulmonic Voiced Dental (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x1d9e"
        Pulmonic Voiceless Alveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "\x02e2"
        Pulmonic Voiced Alveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "\x1dbb"
        Pulmonic Voiceless PostAlveolar (Fricative Sibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x1db4"
        Pulmonic Voiced PostAlveolar (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "\x1dbe"
        Pulmonic Voiceless Palatal (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "\x1d9d"
        Pulmonic Voiced Palatal (Fricative Sibilant) -> Text -> Maybe IPA
mkJustIPA "\x1dbd"
        Pulmonic Voiceless Palatal (Fricative NonSibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x1d9c\x0327"
        Pulmonic Voiced Palatal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x1da8"
        Pulmonic Voiceless Velar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x02e3"
        Pulmonic Voiced Velar (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x02e0"
        Pulmonic Voiceless Uvular (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x1d61"
        Pulmonic Voiced Uvular (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x02b6"
        Pulmonic Voiceless Glottal (Fricative NonSibilant) ->
            Text -> Maybe IPA
mkJustIPA "\x02b0"
        Pulmonic Voiced Glottal (Fricative NonSibilant) -> Text -> Maybe IPA
mkJustIPA "\x02b1"

        Pulmonic Voiced LabioDental Approximant -> Text -> Maybe IPA
mkJustIPA "\x1db9"
        Pulmonic Voiced Alveolar Approximant -> Text -> Maybe IPA
mkJustIPA "\x02b4"
        Pulmonic Voiced Retroflex Approximant -> Text -> Maybe IPA
mkJustIPA "\x02b5"
        Pulmonic Voiced Palatal Approximant -> Text -> Maybe IPA
mkJustIPA "\x02b2"
        Pulmonic Voiceless Velar Approximant -> Text -> Maybe IPA
mkJustIPA "\xab69"
        Pulmonic Voiced Velar Approximant -> Text -> Maybe IPA
mkJustIPA "\x1dad"

        Pulmonic Voiced Alveolar Trill -> Text -> Maybe IPA
mkJustIPA "\x02b3"

        _ -> Maybe IPA
forall a. Maybe a
Nothing

    Vowel Close Front Unrounded -> Text -> Maybe IPA
mkJustIPA "\x2071"
    Vowel Close Front Rounded -> Text -> Maybe IPA
mkJustIPA "\x02b8"
    Vowel Close Central Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1da4"
    Vowel Close Central Rounded -> Text -> Maybe IPA
mkJustIPA "\x1db6"
    Vowel Close Back Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d5a"
    Vowel Close Back Rounded -> Text -> Maybe IPA
mkJustIPA "\x1d58"
    Vowel NearClose Front Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1da6"
    Vowel NearClose Central Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1da7"
    Vowel NearClose Back Rounded -> Text -> Maybe IPA
mkJustIPA "\x1db7"
    Vowel Mid Central Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d4a"
    Vowel Mid Central Rounded -> Text -> Maybe IPA
mkJustIPA "\x1d4a"
    Vowel OpenMid Front Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d4b"
    Vowel OpenMid Front Rounded -> Text -> Maybe IPA
mkJustIPA "\xa7f9"
    Vowel OpenMid Central Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d9f"
    Vowel OpenMid Back Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1dba"
    Vowel OpenMid Back Rounded -> Text -> Maybe IPA
mkJustIPA "\x1d53"
    Vowel NearOpen Front Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d46"
    Vowel NearOpen Central Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d44"
    Vowel NearOpen Back Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d45"
    Vowel NearOpen Back Rounded -> Text -> Maybe IPA
mkJustIPA "\x1d9b"
    Vowel Open Front Unrounded -> Text -> Maybe IPA
mkJustIPA "\x1d43"
    Vowel Open Back Rounded -> Text -> Maybe IPA
mkJustIPA "\x1d44"

    _ -> Maybe IPA
forall a. Maybe a
Nothing

mkJustXSampa :: Text -> Maybe XSampa
mkJustXSampa :: Text -> Maybe XSampa
mkJustXSampa = XSampa -> Maybe XSampa
forall a. a -> Maybe a
Just (XSampa -> Maybe XSampa)
-> (Text -> XSampa) -> Text -> Maybe XSampa
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> XSampa
XSampa

mkXSampaOp :: ReprIPA a => (b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp :: (b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp f :: b -> Maybe XSampa
f x :: a
x y :: b
y = XSampa -> XSampa -> XSampa
forall a. Semigroup a => a -> a -> a
(<>) (XSampa -> XSampa -> XSampa)
-> Maybe XSampa -> Maybe (XSampa -> XSampa)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa a
x Maybe (XSampa -> XSampa) -> Maybe XSampa -> Maybe XSampa
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> b -> Maybe XSampa
f b
y

vowelXSampa :: Segment -> Maybe XSampa
vowelXSampa :: Segment -> Maybe XSampa
vowelXSampa = \case
    Vowel Close Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "i"
    Vowel Close Front Rounded -> Text -> Maybe XSampa
mkJustXSampa "y"
    Vowel Close Central Unrounded -> Text -> Maybe XSampa
mkJustXSampa "1"
    Vowel Close Central Rounded -> Text -> Maybe XSampa
mkJustXSampa "}"
    Vowel Close Back Unrounded -> Text -> Maybe XSampa
mkJustXSampa "M"
    Vowel Close Back Rounded -> Text -> Maybe XSampa
mkJustXSampa "u"
    Vowel NearClose Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "I"
    Vowel NearClose Front Rounded -> Text -> Maybe XSampa
mkJustXSampa "Y"
    Vowel NearClose Back Rounded -> Text -> Maybe XSampa
mkJustXSampa "U"
    Vowel CloseMid Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "e"
    Vowel CloseMid Front Rounded -> Text -> Maybe XSampa
mkJustXSampa "2"
    Vowel CloseMid Central Unrounded -> Text -> Maybe XSampa
mkJustXSampa "@\\"
    Vowel CloseMid Central Rounded -> Text -> Maybe XSampa
mkJustXSampa "8"
    Vowel CloseMid Back Unrounded -> Text -> Maybe XSampa
mkJustXSampa "7"
    Vowel CloseMid Back Rounded -> Text -> Maybe XSampa
mkJustXSampa "o"
    Vowel Mid Front Unrounded -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Front Roundedness
Unrounded)
    Vowel Mid Front Rounded -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Front Roundedness
Rounded)
    Vowel Mid Central Unrounded -> Text -> Maybe XSampa
mkJustXSampa "@"
    Vowel Mid Back Unrounded -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Back Roundedness
Unrounded)
    Vowel Mid Back Rounded -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature SegmentalFeature
Lowered (Height -> Backness -> Roundedness -> Segment
Vowel Height
CloseMid Backness
Back Roundedness
Unrounded)
    Vowel OpenMid Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "E"
    Vowel OpenMid Front Rounded -> Text -> Maybe XSampa
mkJustXSampa "9"
    Vowel OpenMid Central Unrounded -> Text -> Maybe XSampa
mkJustXSampa "3"
    Vowel OpenMid Central Rounded -> Text -> Maybe XSampa
mkJustXSampa "3\\"
    Vowel OpenMid Back Unrounded -> Text -> Maybe XSampa
mkJustXSampa "V"
    Vowel OpenMid Back Rounded -> Text -> Maybe XSampa
mkJustXSampa "O"
    Vowel NearOpen Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "{"
    Vowel NearOpen Central Unrounded -> Text -> Maybe XSampa
mkJustXSampa "6"
    Vowel Open Front Unrounded -> Text -> Maybe XSampa
mkJustXSampa "a"
    Vowel Open Front Rounded -> Text -> Maybe XSampa
mkJustXSampa "&"
    Vowel Open Back Unrounded -> Text -> Maybe XSampa
mkJustXSampa "A"
    Vowel Open Back Rounded -> Text -> Maybe XSampa
mkJustXSampa "Q"
    _ -> Maybe XSampa
forall a. Maybe a
Nothing

consonantXSampa :: Consonant -> Maybe XSampa
consonantXSampa :: Consonant -> Maybe XSampa
consonantXSampa = \case
    -- Pulmonic consonants
    -- Bilabials
    Pulmonic Voiceless Bilabial Nasal -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Bilabial Manner
Nasal)
    Pulmonic Voiced Bilabial Nasal -> Text -> Maybe XSampa
mkJustXSampa "m"
    Pulmonic Voiced Bilabial Plosive -> Text -> Maybe XSampa
mkJustXSampa "b"
    Pulmonic Voiceless Bilabial Plosive -> Text -> Maybe XSampa
mkJustXSampa "p"
    Pulmonic Voiceless Bilabial (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "p\\"
    Pulmonic Voiced Bilabial (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "B"
    Pulmonic Voiced Bilabial Trill -> Text -> Maybe XSampa
mkJustXSampa "B\\"

    -- Labio-dentals
    Pulmonic Voiced LabioDental Nasal -> Text -> Maybe XSampa
mkJustXSampa "F"
    Pulmonic Voiceless LabioDental (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "f"
    Pulmonic Voiced LabioDental (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "v"
    Pulmonic Voiced LabioDental Approximant -> Text -> Maybe XSampa
mkJustXSampa "P"

    -- Dentals
    Pulmonic Voiceless Dental (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "T"
    Pulmonic Voiced Dental (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "D"

    -- Alveolars
    Pulmonic Voiceless Alveolar Nasal -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Nasal)
    Pulmonic Voiced Alveolar Nasal -> Text -> Maybe XSampa
mkJustXSampa "n"
    Pulmonic Voiceless Alveolar Plosive -> Text -> Maybe XSampa
mkJustXSampa "t"
    Pulmonic Voiced Alveolar Plosive -> Text -> Maybe XSampa
mkJustXSampa "d"
    Pulmonic Voiceless Alveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_s"
    Pulmonic Voiced Alveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "d_z"
    Pulmonic Voiceless Alveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s"
    Pulmonic Voiced Alveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "z"
    Pulmonic Voiced Alveolar Approximant -> Text -> Maybe XSampa
mkJustXSampa "r\\"
    Pulmonic Voiceless Alveolar Flap -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Flap)
    Pulmonic Voiced Alveolar Flap -> Text -> Maybe XSampa
mkJustXSampa "4"
    Pulmonic Voiced Alveolar Trill -> Text -> Maybe XSampa
mkJustXSampa "r"
    Pulmonic Voiceless Alveolar Trill -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Alveolar Manner
Trill)
    Pulmonic Voiceless Alveolar LateralFricative -> Text -> Maybe XSampa
mkJustXSampa "K"
    Pulmonic Voiced Alveolar LateralFricative -> Text -> Maybe XSampa
mkJustXSampa "K\\"
    Pulmonic Voiced Alveolar LateralApproximant -> Text -> Maybe XSampa
mkJustXSampa "l"

    -- Post-alveolars
    Pulmonic Voiceless PostAlveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_S"
    Pulmonic Voiced PostAlveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "d_Z"
    Pulmonic Voiceless PostAlveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "S"
    Pulmonic Voiced PostAlveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "Z"

    -- Retroflexes
    Pulmonic Voiceless Retroflex Nasal -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Retroflex Manner
Nasal)
    Pulmonic Voiced Retroflex Nasal -> Text -> Maybe XSampa
mkJustXSampa "n`"
    Pulmonic Voiceless Retroflex Plosive -> Text -> Maybe XSampa
mkJustXSampa "t`"
    Pulmonic Voiced Retroflex Plosive -> Text -> Maybe XSampa
mkJustXSampa "d`"
    Pulmonic Voiceless Retroflex (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t`_s`"
    Pulmonic Voiced Retroflex (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "d`_z`"
    Pulmonic Voiceless Retroflex (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s`"
    Pulmonic Voiced Retroflex (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "z`"
    Pulmonic Voiced Retroflex Approximant -> Text -> Maybe XSampa
mkJustXSampa "r\\`"
    Pulmonic Voiceless Retroflex Flap -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Retroflex Manner
Nasal)
    Pulmonic Voiced Retroflex Flap -> Text -> Maybe XSampa
mkJustXSampa "r`"
    Pulmonic Voiceless Retroflex LateralApproximant -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Retroflex Manner
Nasal)
    Pulmonic Voiced Retroflex LateralApproximant -> Text -> Maybe XSampa
mkJustXSampa "l`"

    -- Palatals
    Pulmonic Voiced Palatal Nasal -> Text -> Maybe XSampa
mkJustXSampa "J"
    Pulmonic Voiceless Palatal Plosive -> Text -> Maybe XSampa
mkJustXSampa "c"
    Pulmonic Voiced Palatal Plosive -> Text -> Maybe XSampa
mkJustXSampa "J\\"
    Pulmonic Voiceless Palatal (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_s\\"
    Pulmonic Voiced Palatal (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "d_z\\"
    Pulmonic Voiceless Palatal (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s\\"
    Pulmonic Voiced Palatal (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "z\\"
    Pulmonic Voiceless Palatal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "C"
    Pulmonic Voiced Palatal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "j\\"
    Pulmonic Voiced Palatal Approximant -> Text -> Maybe XSampa
mkJustXSampa "j"
    Pulmonic Voiced Palatal LateralApproximant -> Text -> Maybe XSampa
mkJustXSampa "L"

    -- Velars
    Pulmonic Voiceless Velar Nasal -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Velar Manner
Nasal)
    Pulmonic Voiced Velar Nasal -> Text -> Maybe XSampa
mkJustXSampa "N"
    Pulmonic Voiceless Velar Plosive -> Text -> Maybe XSampa
mkJustXSampa "k"
    Pulmonic Voiced Velar Plosive -> Text -> Maybe XSampa
mkJustXSampa "g"
    Pulmonic Voiceless Velar (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "k_x"
    Pulmonic Voiced Velar (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "g_G"
    Pulmonic Voiceless Velar (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "x"
    Pulmonic Voiced Velar (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "G"
    Pulmonic Voiced Velar Approximant -> Text -> Maybe XSampa
mkJustXSampa "m\\"
    Pulmonic Voiced Velar LateralApproximant -> Text -> Maybe XSampa
mkJustXSampa "L\\"

    -- Uvulars
    Pulmonic Voiced Uvular Nasal -> Text -> Maybe XSampa
mkJustXSampa "N\\"
    Pulmonic Voiceless Uvular Plosive -> Text -> Maybe XSampa
mkJustXSampa "q"
    Pulmonic Voiced Uvular Plosive -> Text -> Maybe XSampa
mkJustXSampa "G\\"
    Pulmonic Voiceless Uvular (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "q_X"
    Pulmonic Voiced Uvular (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "G\\_R"
    Pulmonic Voiceless Uvular (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "X"
    Pulmonic Voiced Uvular (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "R"
    Pulmonic Voiceless Uvular Trill -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Manner -> Segment
PulmonicConsonant Phonation
Voiced Place
Uvular Manner
Trill)
    Pulmonic Voiced Uvular Trill -> Text -> Maybe XSampa
mkJustXSampa "R\\"

    -- Pharyngeals
    Pulmonic Voiceless Pharyngeal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "X\\"
    Pulmonic Voiced Pharyngeal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "?\\"

    -- Glottals
    Pulmonic Voiceless Glottal Plosive -> Text -> Maybe XSampa
mkJustXSampa "?"
    Pulmonic Voiceless Glottal (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "?_h\\"
    Pulmonic Voiceless Glottal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "h"
    Pulmonic Voiced Glottal (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "h\\"

    -- Ejectives
    -- Bilabials
    Ejective Bilabial Plosive -> Text -> Maybe XSampa
mkJustXSampa "p_>"
    Ejective Bilabial (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "p\\_>"

    -- Dentals
    Ejective Dental (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "T_>"

    -- Alveolars
    Ejective Alveolar Plosive -> Text -> Maybe XSampa
mkJustXSampa "t_>"
    Ejective Alveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_s_>"
    Ejective Alveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s_>"

    -- Post-alveolars
    Ejective PostAlveolar (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_S_>"
    Ejective PostAlveolar (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "S_>"

    -- Retroflexes
    Ejective Retroflex Plosive -> Text -> Maybe XSampa
mkJustXSampa "t`_>"
    Ejective Retroflex (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t`_s`_>"
    Ejective Retroflex (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s`_>"

    -- Palatals
    Ejective Palatal Plosive -> Text -> Maybe XSampa
mkJustXSampa "c_>"
    Ejective Palatal (Affricate Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "t_s\\_>"
    Ejective Palatal (Fricative Sibilant) -> Text -> Maybe XSampa
mkJustXSampa "s\\_>"

    -- Velars
    Ejective Velar Plosive -> Text -> Maybe XSampa
mkJustXSampa "k_>"
    Ejective Velar (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "k_x_>"
    Ejective Velar (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "x_>"

    -- Uvulars
    Ejective Uvular Plosive -> Text -> Maybe XSampa
mkJustXSampa "q_>"
    Ejective Uvular (Affricate NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "q_X_>"
    Ejective Uvular (Fricative NonSibilant) -> Text -> Maybe XSampa
mkJustXSampa "X_>"

    -- Implosives
    Implosive Voiceless Bilabial -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Bilabial)
    Implosive Voiced Bilabial -> Text -> Maybe XSampa
mkJustXSampa "b_<"
    Implosive Voiceless Alveolar -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Alveolar)
    Implosive Voiced Alveolar -> Text -> Maybe XSampa
mkJustXSampa "d_<"
    Implosive Voiceless Retroflex -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Retroflex)
    Implosive Voiced Retroflex -> Text -> Maybe XSampa
mkJustXSampa "d`_<"
    Implosive Voiceless Palatal -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Palatal)
    Implosive Voiced Palatal -> Text -> Maybe XSampa
mkJustXSampa "f_<"
    Implosive Voiceless Velar -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Palatal)
    Implosive Voiced Velar -> Text -> Maybe XSampa
mkJustXSampa "g_<"
    Implosive Voiceless Uvular -> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Phonation -> Place -> Segment
ImplosiveConsonant Phonation
Voiced Place
Uvular)
    Implosive Voiced Uvular -> Text -> Maybe XSampa
mkJustXSampa "G_<"

    -- Clicks
    Click Bilabial -> Text -> Maybe XSampa
mkJustXSampa "O\\"
    Click Dental -> Text -> Maybe XSampa
mkJustXSampa "|\\"
    Click Alveolar -> Text -> Maybe XSampa
mkJustXSampa "ǃ\\"
    Click PostAlveolar -> Text -> Maybe XSampa
mkJustXSampa "|\\|\\" -- lateral click
    Click Palatal -> Text -> Maybe XSampa
mkJustXSampa "=\\"

    -- Double articulation
    DoublyArticulated Voiced Bilabial Alveolar Nasal -> Text -> Maybe XSampa
mkJustXSampa "n_m"
    DoublyArticulated Voiceless Bilabial Alveolar Plosive -> Text -> Maybe XSampa
mkJustXSampa "t_p"
    DoublyArticulated Voiced Bilabial Alveolar Plosive -> Text -> Maybe XSampa
mkJustXSampa "d_b"
    DoublyArticulated Voiced Bilabial Velar Nasal -> Text -> Maybe XSampa
mkJustXSampa "N_m"
    DoublyArticulated Voiceless Bilabial Velar Plosive -> Text -> Maybe XSampa
mkJustXSampa "k_p"
    DoublyArticulated Voiced Bilabial Velar Plosive -> Text -> Maybe XSampa
mkJustXSampa "g_b"
    DoublyArticulated Voiceless Bilabial Palatal (Fricative NonSibilant) ->
        Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Segment -> Maybe XSampa) -> Segment -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SegmentalFeature -> Segment -> Segment
WithSegmentalFeature (Phonation -> SegmentalFeature
Voicing Phonation
Voiceless)
                               (Consonant -> Segment
Consonant (Phonation -> Place -> Place -> Manner -> Consonant
DoublyArticulated Phonation
Voiced
                                                             Place
Bilabial
                                                             Place
Palatal
                                                             Manner
Approximant))
    DoublyArticulated Voiced Bilabial Palatal Approximant -> Text -> Maybe XSampa
mkJustXSampa "H"
    DoublyArticulated Voiceless Bilabial Velar (Fricative NonSibilant) ->
        Text -> Maybe XSampa
mkJustXSampa "W"
    DoublyArticulated Voiced Bilabial Velar Approximant -> Text -> Maybe XSampa
mkJustXSampa "w"
    DoublyArticulated Voiceless PostAlveolar Velar (Fricative Sibilant) ->
        Text -> Maybe XSampa
mkJustXSampa "x\\"
    DoublyArticulated Voiceless LabioDental Velar (Fricative Sibilant) ->
        Text -> Maybe XSampa
mkJustXSampa "x\\"

    _ -> Maybe XSampa
forall a. Maybe a
Nothing

withSegmentalFeatureXSampa :: Segment -> SegmentalFeature -> Maybe XSampa
withSegmentalFeatureXSampa :: Segment -> SegmentalFeature -> Maybe XSampa
withSegmentalFeatureXSampa s :: Segment
s = \case
    Voicing v :: Phonation
v -> (Phonation -> Maybe XSampa) -> Segment -> Phonation -> Maybe XSampa
forall a b.
ReprIPA a =>
(b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp Phonation -> Maybe XSampa
xSampaVoicing Segment
s Phonation
v
      where
        xSampaVoicing :: Phonation -> Maybe XSampa
xSampaVoicing = \case
            Voiceless -> Text -> Maybe XSampa
mkJustXSampa "_0"
            Voiced    -> Text -> Maybe XSampa
mkJustXSampa "_v"
    Length l :: Length
l -> (Length -> Maybe XSampa) -> Segment -> Length -> Maybe XSampa
forall a b.
ReprIPA a =>
(b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp Length -> Maybe XSampa
xSampaLength Segment
s Length
l
      where
        xSampaLength :: Length -> Maybe XSampa
xSampaLength = \case
            OverLong   -> Text -> Maybe XSampa
mkJustXSampa "::"
            Long       -> Text -> Maybe XSampa
mkJustXSampa ":"
            HalfLong   -> Text -> Maybe XSampa
mkJustXSampa ":\\"
            Short      -> Text -> Maybe XSampa
mkJustXSampa Text
forall a. Monoid a => a
mempty
            ExtraShort -> Text -> Maybe XSampa
mkJustXSampa "_X"
    SecondaryArticulation _ -> Maybe XSampa
forall a. Maybe a
Nothing
    SuperScriptNumeric _ -> Maybe XSampa
forall a. Maybe a
Nothing
    feature :: SegmentalFeature
feature -> XSampa -> XSampa -> XSampa
forall a. Semigroup a => a -> a -> a
(<>) (XSampa -> XSampa -> XSampa)
-> Maybe XSampa -> Maybe (XSampa -> XSampa)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Segment -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa Segment
s Maybe (XSampa -> XSampa) -> Maybe XSampa -> Maybe XSampa
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> case SegmentalFeature
feature of
        Aspirated           -> Text -> Maybe XSampa
mkJustXSampa "_h"
        MoreRounded         -> Text -> Maybe XSampa
mkJustXSampa "_O"
        LessRounded         -> Text -> Maybe XSampa
mkJustXSampa "_c"
        Advanced            -> Text -> Maybe XSampa
mkJustXSampa "_+"
        Retracted           -> Text -> Maybe XSampa
mkJustXSampa "_-"
        Centralized         -> Text -> Maybe XSampa
mkJustXSampa "_\""
        MidCentralized      -> Text -> Maybe XSampa
mkJustXSampa "_x"
        Syllabic            -> Text -> Maybe XSampa
mkJustXSampa "="
        NonSyllabic         -> Text -> Maybe XSampa
mkJustXSampa "_^"
        Rhotacized          -> Text -> Maybe XSampa
mkJustXSampa "`"
        BreathyVoice        -> Text -> Maybe XSampa
mkJustXSampa "_t"
        CreakyVoice         -> Text -> Maybe XSampa
mkJustXSampa "_k"
        Labialized          -> Text -> Maybe XSampa
mkJustXSampa "_w"
        Palatalized         -> Text -> Maybe XSampa
mkJustXSampa "'"
        Velarized           -> Text -> Maybe XSampa
mkJustXSampa "_G"
        Pharyngealized      -> Text -> Maybe XSampa
mkJustXSampa "_?\\"
        Raised              -> Text -> Maybe XSampa
mkJustXSampa "_r"
        Lowered             -> Text -> Maybe XSampa
mkJustXSampa "_o"
        AdvancedTongueRoot  -> Text -> Maybe XSampa
mkJustXSampa "_A"
        RetractedTongueRoot -> Text -> Maybe XSampa
mkJustXSampa "_q"
        Dentalized          -> Text -> Maybe XSampa
mkJustXSampa "_d"
        Apical              -> Text -> Maybe XSampa
mkJustXSampa "_a"
        Laminal             -> Text -> Maybe XSampa
mkJustXSampa "_m"
        Nasalized           -> Text -> Maybe XSampa
mkJustXSampa "~"
        LateralRelease      -> Text -> Maybe XSampa
mkJustXSampa "_l"
        NoAudibleRelease    -> Text -> Maybe XSampa
mkJustXSampa "_}"
        _                   -> Maybe XSampa
forall a. Maybe a
Nothing

withSuprasegmentalFeatureXSampa
    :: Traversable t => Syllable t -> SuprasegmentalFeature -> Maybe XSampa
withSuprasegmentalFeatureXSampa :: Syllable t -> SuprasegmentalFeature -> Maybe XSampa
withSuprasegmentalFeatureXSampa s :: Syllable t
s = \case
    LevelLexicalTone tone :: LevelTone
tone -> (LevelTone -> Maybe XSampa)
-> Syllable t -> LevelTone -> Maybe XSampa
forall a b.
ReprIPA a =>
(b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp LevelTone -> Maybe XSampa
ipaTone Syllable t
s LevelTone
tone
      where
        ipaTone :: LevelTone -> Maybe XSampa
ipaTone = \case
            ExtraHighTone -> Text -> Maybe XSampa
mkJustXSampa "_T"
            HighTone      -> Text -> Maybe XSampa
mkJustXSampa "_H"
            MidTone       -> Text -> Maybe XSampa
mkJustXSampa "_M"
            LowTone       -> Text -> Maybe XSampa
mkJustXSampa "_L"
            ExtraLowTone  -> Text -> Maybe XSampa
mkJustXSampa "_B"
            DownStep      -> Text -> Maybe XSampa
mkJustXSampa "!"
            UpStep        -> Text -> Maybe XSampa
mkJustXSampa "^"

    LevelLexicalToneDiacritic tone :: LevelTone
tone -> Syllable t -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Syllable t -> Maybe XSampa) -> Syllable t -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SuprasegmentalFeature -> Syllable t -> Syllable t
forall (t :: * -> *).
SuprasegmentalFeature -> Syllable t -> Syllable t
WithSuprasegmentalFeature (LevelTone -> SuprasegmentalFeature
LevelLexicalTone LevelTone
tone) Syllable t
s

    LexicalToneContour tone :: ToneContour
tone -> (ToneContour -> Maybe XSampa)
-> Syllable t -> ToneContour -> Maybe XSampa
forall a b.
ReprIPA a =>
(b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp ToneContour -> Maybe XSampa
ipaToneContour Syllable t
s ToneContour
tone
      where
        ipaToneContour :: ToneContour -> Maybe XSampa
ipaToneContour = \case
            Rising        -> Text -> Maybe XSampa
mkJustXSampa "_R"
            Falling       -> Text -> Maybe XSampa
mkJustXSampa "_F"
            HighRising    -> Text -> Maybe XSampa
mkJustXSampa "_H_T"
            LowRising     -> Text -> Maybe XSampa
mkJustXSampa "_B_L"
            HighFalling   -> Text -> Maybe XSampa
mkJustXSampa "_H_F"
            LowFalling    -> Text -> Maybe XSampa
mkJustXSampa "_L_B"
            RisingFalling -> Text -> Maybe XSampa
mkJustXSampa "_R_F"
            FallingRising -> Text -> Maybe XSampa
mkJustXSampa "_F_R"
            GlobalRise    -> Text -> Maybe XSampa
mkJustXSampa "<R>"
            GlobalFall    -> Text -> Maybe XSampa
mkJustXSampa "<F>"

    LexicalToneContourDiacritic tone :: ToneContour
tone -> Syllable t -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa
        (Syllable t -> Maybe XSampa) -> Syllable t -> Maybe XSampa
forall a b. (a -> b) -> a -> b
$ SuprasegmentalFeature -> Syllable t -> Syllable t
forall (t :: * -> *).
SuprasegmentalFeature -> Syllable t -> Syllable t
WithSuprasegmentalFeature (ToneContour -> SuprasegmentalFeature
LexicalToneContour ToneContour
tone) Syllable t
s

    Stress stress :: Stress
stress -> (Stress -> Maybe XSampa) -> Syllable t -> Stress -> Maybe XSampa
forall a b.
ReprIPA a =>
(b -> Maybe XSampa) -> a -> b -> Maybe XSampa
mkXSampaOp Stress -> Maybe XSampa
ipaStress Syllable t
s Stress
stress
      where
        ipaStress :: Stress -> Maybe XSampa
ipaStress Primary   = Text -> Maybe XSampa
mkJustXSampa "\""
        ipaStress Secondary = Text -> Maybe XSampa
mkJustXSampa "%"

    -- Explicit syllable break
    Break -> XSampa -> XSampa -> XSampa
forall a. Semigroup a => a -> a -> a
(<>) (XSampa -> XSampa -> XSampa)
-> Maybe XSampa -> Maybe (XSampa -> XSampa)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Syllable t -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa Syllable t
s Maybe (XSampa -> XSampa) -> Maybe XSampa -> Maybe XSampa
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe XSampa
mkJustXSampa "."

    -- Syllable non-break
    Linking -> XSampa -> XSampa -> XSampa
forall a. Semigroup a => a -> a -> a
(<>) (XSampa -> XSampa -> XSampa)
-> Maybe XSampa -> Maybe (XSampa -> XSampa)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Syllable t -> Maybe XSampa
forall a. ReprIPA a => a -> Maybe XSampa
toXSampa Syllable t
s Maybe (XSampa -> XSampa) -> Maybe XSampa -> Maybe XSampa
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Maybe XSampa
mkJustXSampa "-\\"