Copyright | (c) 2021 Rory Tyler Hayford |
---|---|
License | BSD-3-Clause |
Maintainer | rory.hayford@protonmail.com |
Stability | experimental |
Portability | GHC Types representing segments representable in the IPA |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype IPA = IPA {}
- mkIPA :: Text -> IPA
- newtype XSampa = XSampa {}
- mkXSampa :: Text -> Maybe XSampa
- data Segment
- data Consonant
- pattern PulmonicConsonant :: Phonation -> Place -> Manner -> Segment
- pattern EjectiveConsonant :: Place -> Manner -> Segment
- pattern ClickConsonant :: Place -> Segment
- pattern ImplosiveConsonant :: Phonation -> Place -> Segment
- pattern DoublyArticulatedConsonant :: Phonation -> Place -> Place -> Manner -> Segment
- data Manner
- data Place
- data Phonation
- data Sibilance
- data Vowel
- pattern PureVowel :: Height -> Backness -> Roundedness -> Segment
- pattern Diphthong :: Vowel -> Vowel -> Segment
- pattern Triphthong :: Vowel -> Vowel -> Vowel -> Segment
- data Height
- data Backness
- data Roundedness
- type MultiSegment t = (Applicative t, Traversable t, Monoid (t Segment))
- data Syllable t
- data SuprasegmentalFeature
- data ToneContour
- data LevelTone
- data Stress
- data Length
- = OverLong
- | HalfLong
- | Long
- | Short
- | ExtraShort
- data SegmentalFeature
- = Voicing Phonation
- | Length Length
- | SecondaryArticulation Segment
- | Aspirated
- | MoreRounded
- | LessRounded
- | Advanced
- | Retracted
- | Centralized
- | MidCentralized
- | Compressed
- | Syllabic
- | NonSyllabic
- | Rhotacized
- | BreathyVoice
- | CreakyVoice
- | LinguoLabialized
- | Labialized
- | Palatalized
- | Velarized
- | Pharyngealized
- | Raised
- | Lowered
- | AdvancedTongueRoot
- | RetractedTongueRoot
- | Dentalized
- | Apical
- | Laminal
- | Nasalized
- | NasalRelease
- | LateralRelease
- | NoAudibleRelease
- data Delimiter
- data IPAException
Notation systems
Textual representation of a speech segment or grouping of segments, with
zero or more articulatory features; encoded in IPA transcription. Note this
has a Semigroup
instance, so various IPA
s can conveniently be concatenated
with <>
X-SAMPA is an ASCII encoding of the IPA (ca. 1993). Note that fewer
transcriptions are possible using X-SAMPA than the IPA, so certain valid
IPA
Segment
s have no direct equivalence using XSampa
. As with IPA
,
XSampa
is an instance of Semigroup
Segments
A single segment, or combination of a segment and articulatory feature
Consonant Consonant | Pulmonic and non-pulmonic consonants |
Vowel Vowel | Monoph-, diph-, and triphthongs |
Zero | A null/zero phone |
WithSegmentalFeature SegmentalFeature Segment | Various other articulatory features |
Optional Segment | A segment that is conventionally surrounded by parentheses. This is not an official part of the IPA, but is nevertheless encountered fairly frequently in IPA notation in the wild |
Instances
Consonants (pulmonic and non-pulmonic)
Pulmonic and non-pulmonic consonants
Pulmonic Phonation Place Manner | |
Ejective Place Manner | |
Implosive Phonation Place | |
Click Place |
|
DoublyArticulated Phonation Place Place Manner |
Instances
Convenience patterns
These are convenience patterns for creating different types of Consonant
Segment
s, as the nesting of data constructors might otherwise be somewhat
tiresome
pattern ClickConsonant :: Place -> Segment Source #
Consonant features
Consonantal manner of articulation
Nasal | |
Plosive | |
Fricative Sibilance | |
Affricate Sibilance | |
Approximant | |
Flap | |
Trill | |
LateralAffricate | |
LateralFricative | |
LateralApproximant | |
LateralFlap |
Instances
Eq Manner Source # | |
Data Manner Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Manner -> c Manner # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Manner # toConstr :: Manner -> Constr # dataTypeOf :: Manner -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Manner) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Manner) # gmapT :: (forall b. Data b => b -> b) -> Manner -> Manner # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Manner -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Manner -> r # gmapQ :: (forall d. Data d => d -> u) -> Manner -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Manner -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Manner -> m Manner # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Manner -> m Manner # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Manner -> m Manner # | |
Show Manner Source # | |
Generic Manner Source # | |
Lift Manner Source # | |
type Rep Manner Source # | |
Defined in Language.IPA.Types type Rep Manner = D1 ('MetaData "Manner" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) (((C1 ('MetaCons "Nasal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Plosive" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Fricative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sibilance)) :+: (C1 ('MetaCons "Affricate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Sibilance)) :+: C1 ('MetaCons "Approximant" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Flap" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Trill" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LateralAffricate" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LateralFricative" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LateralApproximant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LateralFlap" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Consonantal place of articulation
Bilabial | |
LabioDental | |
LinguoLabial | |
Dental | |
Alveolar | |
PostAlveolar | |
Retroflex | |
Palatal | |
Velar | |
Uvular | |
Pharyngeal | |
Glottal |
Instances
Eq Place Source # | |
Data Place Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Place -> c Place # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Place # dataTypeOf :: Place -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Place) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Place) # gmapT :: (forall b. Data b => b -> b) -> Place -> Place # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Place -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Place -> r # gmapQ :: (forall d. Data d => d -> u) -> Place -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Place -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Place -> m Place # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Place -> m Place # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Place -> m Place # | |
Ord Place Source # | |
Show Place Source # | |
Generic Place Source # | |
Lift Place Source # | |
type Rep Place Source # | |
Defined in Language.IPA.Types type Rep Place = D1 ('MetaData "Place" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) (((C1 ('MetaCons "Bilabial" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LabioDental" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinguoLabial" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Dental" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Alveolar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PostAlveolar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Retroflex" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Palatal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Velar" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Uvular" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Pharyngeal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Glottal" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Phonation (voicing)
Instances
Eq Phonation Source # | |
Data Phonation Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Phonation -> c Phonation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Phonation # toConstr :: Phonation -> Constr # dataTypeOf :: Phonation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Phonation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Phonation) # gmapT :: (forall b. Data b => b -> b) -> Phonation -> Phonation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Phonation -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Phonation -> r # gmapQ :: (forall d. Data d => d -> u) -> Phonation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Phonation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Phonation -> m Phonation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Phonation -> m Phonation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Phonation -> m Phonation # | |
Show Phonation Source # | |
Generic Phonation Source # | |
Lift Phonation Source # | |
type Rep Phonation Source # | |
Sibilance for fricative consonants
Instances
Eq Sibilance Source # | |
Data Sibilance Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sibilance -> c Sibilance # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Sibilance # toConstr :: Sibilance -> Constr # dataTypeOf :: Sibilance -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Sibilance) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Sibilance) # gmapT :: (forall b. Data b => b -> b) -> Sibilance -> Sibilance # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sibilance -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sibilance -> r # gmapQ :: (forall d. Data d => d -> u) -> Sibilance -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Sibilance -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sibilance -> m Sibilance # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sibilance -> m Sibilance # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sibilance -> m Sibilance # | |
Show Sibilance Source # | |
Generic Sibilance Source # | |
Lift Sibilance Source # | |
type Rep Sibilance Source # | |
Vowels
Vowel type. Note that this type does not prevent the construction of
nonsensical vowel values such as Diphthong (Diphthong ...) (Diphthong ...)
Instances
Convenience patterns
Vowel features
Vowel height
Instances
Eq Height Source # | |
Data Height Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Height -> c Height # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Height # toConstr :: Height -> Constr # dataTypeOf :: Height -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Height) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Height) # gmapT :: (forall b. Data b => b -> b) -> Height -> Height # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Height -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Height -> r # gmapQ :: (forall d. Data d => d -> u) -> Height -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Height -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Height -> m Height # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Height -> m Height # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Height -> m Height # | |
Show Height Source # | |
Generic Height Source # | |
Lift Height Source # | |
type Rep Height Source # | |
Defined in Language.IPA.Types type Rep Height = D1 ('MetaData "Height" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) ((C1 ('MetaCons "Close" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NearClose" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CloseMid" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Mid" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpenMid" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NearOpen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Open" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Vowel backness
Instances
Eq Backness Source # | |
Data Backness Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Backness -> c Backness # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Backness # toConstr :: Backness -> Constr # dataTypeOf :: Backness -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Backness) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Backness) # gmapT :: (forall b. Data b => b -> b) -> Backness -> Backness # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Backness -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Backness -> r # gmapQ :: (forall d. Data d => d -> u) -> Backness -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Backness -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Backness -> m Backness # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Backness -> m Backness # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Backness -> m Backness # | |
Ord Backness Source # | |
Defined in Language.IPA.Types | |
Show Backness Source # | |
Generic Backness Source # | |
Lift Backness Source # | |
type Rep Backness Source # | |
Defined in Language.IPA.Types type Rep Backness = D1 ('MetaData "Backness" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) ((C1 ('MetaCons "Front" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NearFront" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Central" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NearBack" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Back" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data Roundedness Source #
Vowel roundedness
Instances
Suprasegmentals
type MultiSegment t = (Applicative t, Traversable t, Monoid (t Segment)) Source #
Constraint synonym for syllable containers
Multiple segments, or combination of multiple segments with suprasegmental feature
Syllable (t Segment) | A grouping of segments without extra suprasegmental information |
WithSuprasegmentalFeature SuprasegmentalFeature (Syllable t) | Articulatory features that affect/encompass the entire syllable |
Instances
Lift (t Segment) => Lift (Syllable t :: Type) Source # | |
Eq (t Segment) => Eq (Syllable t) Source # | |
(Data (t Segment), Typeable t) => Data (Syllable t) Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Syllable t -> c (Syllable t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Syllable t) # toConstr :: Syllable t -> Constr # dataTypeOf :: Syllable t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Syllable t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Syllable t)) # gmapT :: (forall b. Data b => b -> b) -> Syllable t -> Syllable t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syllable t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syllable t -> r # gmapQ :: (forall d. Data d => d -> u) -> Syllable t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Syllable t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Syllable t -> m (Syllable t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Syllable t -> m (Syllable t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Syllable t -> m (Syllable t) # | |
Show (t Segment) => Show (Syllable t) Source # | |
Generic (Syllable t) Source # | |
MultiSegment t => ReprXSampa (Syllable t) Source # | |
Defined in Language.IPA.Class | |
MultiSegment t => ReprIPA (Syllable t) Source # | |
type Rep (Syllable t) Source # | |
Defined in Language.IPA.Types type Rep (Syllable t) = D1 ('MetaData "Syllable" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) (C1 ('MetaCons "Syllable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (t Segment))) :+: C1 ('MetaCons "WithSuprasegmentalFeature" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SuprasegmentalFeature) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Syllable t)))) |
Suprasegmental features
data SuprasegmentalFeature Source #
LevelLexicalTone LevelTone | Level lexical tones in Chao letters |
LevelLexicalToneDiacritic LevelTone | Level lexical tones, diacritic. The tone is a combining character |
LexicalToneContour ToneContour | Lexical tone contours in Chao letters |
LexicalToneContourDiacritic ToneContour | Lexical tone contours, as diacritics. Each contour is a combining character |
ToneNumber Int | |
Stress Stress | Syllable stress |
Break | Explicit syllable break |
Linking | Absence of a break |
Instances
data ToneContour Source #
Lexical tone represented as a contour
Rising | |
Falling | |
HighRising | |
LowRising | |
HighFalling | |
LowFalling | |
RisingFalling | |
FallingRising | |
GlobalRise | |
GlobalFall |
Instances
Lexical tone with Chao-style tone letters
Instances
Eq LevelTone Source # | |
Data LevelTone Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LevelTone -> c LevelTone # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LevelTone # toConstr :: LevelTone -> Constr # dataTypeOf :: LevelTone -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LevelTone) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LevelTone) # gmapT :: (forall b. Data b => b -> b) -> LevelTone -> LevelTone # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LevelTone -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LevelTone -> r # gmapQ :: (forall d. Data d => d -> u) -> LevelTone -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LevelTone -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LevelTone -> m LevelTone # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LevelTone -> m LevelTone # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LevelTone -> m LevelTone # | |
Ord LevelTone Source # | |
Defined in Language.IPA.Types | |
Show LevelTone Source # | |
Generic LevelTone Source # | |
Lift LevelTone Source # | |
type Rep LevelTone Source # | |
Defined in Language.IPA.Types type Rep LevelTone = D1 ('MetaData "LevelTone" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) ((C1 ('MetaCons "ExtraHighTone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "HighTone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MidTone" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LowTone" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtraLowTone" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DownStep" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UpStep" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Instances
Eq Stress Source # | |
Data Stress Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stress -> c Stress # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stress # toConstr :: Stress -> Constr # dataTypeOf :: Stress -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stress) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stress) # gmapT :: (forall b. Data b => b -> b) -> Stress -> Stress # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stress -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stress -> r # gmapQ :: (forall d. Data d => d -> u) -> Stress -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Stress -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stress -> m Stress # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stress -> m Stress # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stress -> m Stress # | |
Ord Stress Source # | |
Show Stress Source # | |
Generic Stress Source # | |
Lift Stress Source # | |
type Rep Stress Source # | |
Segmental articulatory features
Vowel length; also serves as a notation for consonant gemination in the IPA
OverLong | |
HalfLong | |
Long | |
Short | The default/unmarked length; using this constructor doesn't affect the default IPA representation of the segment |
ExtraShort |
Instances
Eq Length Source # | |
Data Length Source # | |
Defined in Language.IPA.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Length -> c Length # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Length # toConstr :: Length -> Constr # dataTypeOf :: Length -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Length) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Length) # gmapT :: (forall b. Data b => b -> b) -> Length -> Length # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Length -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Length -> r # gmapQ :: (forall d. Data d => d -> u) -> Length -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Length -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Length -> m Length # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Length -> m Length # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Length -> m Length # | |
Ord Length Source # | |
Show Length Source # | |
Generic Length Source # | |
Lift Length Source # | |
type Rep Length Source # | |
Defined in Language.IPA.Types type Rep Length = D1 ('MetaData "Length" "Language.IPA.Types" "ipa-0.3.1-inplace" 'False) ((C1 ('MetaCons "OverLong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HalfLong" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Long" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Short" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExtraShort" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data SegmentalFeature Source #
Various articulatory features with a diacritic represenation in the IPA.
These can be combined with Segment
s using the WithSegmentalFeature
constructor of that type to produce a Segment
annotated with a given
articulatory feature, e.g.:
>>>
toIPA $ WithSegmentalFeature (Length Long) (Vowel Close Front Unrounded)
Just (IPA "i\720") -- iː
Instances
Transcription delimiters
Transcription delimiters/brackets
Phonetic | Actual pronunciation, transcribed with square brackets, [ .. ] |
Phonemic | Abstract phonemic representation, transcribed with slashes, / .. / |
Errors
data IPAException Source #