ipa-0.3.1.1: Internal Phonetic Alphabet (IPA)
Copyright(c) 2021 Rory Tyler Hayford
LicenseBSD-3-Clause
Maintainerrory.hayford@protonmail.com
Stabilityexperimental
PortabilityGHC Types representing segments representable in the IPA
Safe HaskellNone
LanguageHaskell2010

Language.IPA.Types

Description

 
Synopsis

Notation systems

newtype IPA Source #

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 IPAs can conveniently be concatenated with <>

Constructors

IPA 

Fields

Instances

Instances details
Eq IPA Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: IPA -> IPA -> Bool #

(/=) :: IPA -> IPA -> Bool #

Show IPA Source # 
Instance details

Defined in Language.IPA.Types

Methods

showsPrec :: Int -> IPA -> ShowS #

show :: IPA -> String #

showList :: [IPA] -> ShowS #

Generic IPA Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep IPA :: Type -> Type #

Methods

from :: IPA -> Rep IPA x #

to :: Rep IPA x -> IPA #

Semigroup IPA Source # 
Instance details

Defined in Language.IPA.Types

Methods

(<>) :: IPA -> IPA -> IPA #

sconcat :: NonEmpty IPA -> IPA #

stimes :: Integral b => b -> IPA -> IPA #

type Rep IPA Source # 
Instance details

Defined in Language.IPA.Types

type Rep IPA = D1 ('MetaData "IPA" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'True) (C1 ('MetaCons "IPA" 'PrefixI 'True) (S1 ('MetaSel ('Just "unIPA") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkIPA :: Text -> IPA Source #

normalizes Text value to NFC before wrapping it in IPA. This is to ensure the comparability of IPA values

newtype XSampa Source #

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 Segments have no direct equivalence using XSampa. As with IPA, XSampa is an instance of Semigroup

Constructors

XSampa 

Fields

Instances

Instances details
Eq XSampa Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: XSampa -> XSampa -> Bool #

(/=) :: XSampa -> XSampa -> Bool #

Show XSampa Source # 
Instance details

Defined in Language.IPA.Types

Generic XSampa Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep XSampa :: Type -> Type #

Methods

from :: XSampa -> Rep XSampa x #

to :: Rep XSampa x -> XSampa #

Semigroup XSampa Source # 
Instance details

Defined in Language.IPA.Types

type Rep XSampa Source # 
Instance details

Defined in Language.IPA.Types

type Rep XSampa = D1 ('MetaData "XSampa" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'True) (C1 ('MetaCons "XSampa" 'PrefixI 'True) (S1 ('MetaSel ('Just "unXSampa") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

mkXSampa :: Text -> Maybe XSampa Source #

Wraps a Text value in XSampa, provided the text only contains ASCII characters

Segments

data Segment Source #

A single segment, or combination of a segment and articulatory feature

Constructors

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

Instances details
Eq Segment Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Segment -> Segment -> Bool #

(/=) :: Segment -> Segment -> Bool #

Data Segment Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Segment -> c Segment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Segment #

toConstr :: Segment -> Constr #

dataTypeOf :: Segment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Segment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Segment) #

gmapT :: (forall b. Data b => b -> b) -> Segment -> Segment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Segment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Segment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Segment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Segment -> m Segment #

Show Segment Source # 
Instance details

Defined in Language.IPA.Types

Generic Segment Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Segment :: Type -> Type #

Methods

from :: Segment -> Rep Segment x #

to :: Rep Segment x -> Segment #

ReprXSampa Segment Source # 
Instance details

Defined in Language.IPA.Class

ReprIPA Segment Source # 
Instance details

Defined in Language.IPA.Class

Lift Segment Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Segment -> Q Exp #

liftTyped :: Segment -> Q (TExp Segment) #

type Rep Segment Source # 
Instance details

Defined in Language.IPA.Types

Consonants (pulmonic and non-pulmonic)

data Consonant Source #

Pulmonic and non-pulmonic consonants

Instances

Instances details
Eq Consonant Source # 
Instance details

Defined in Language.IPA.Types

Data Consonant Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Consonant -> c Consonant #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Consonant #

toConstr :: Consonant -> Constr #

dataTypeOf :: Consonant -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Consonant) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Consonant) #

gmapT :: (forall b. Data b => b -> b) -> Consonant -> Consonant #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Consonant -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Consonant -> r #

gmapQ :: (forall d. Data d => d -> u) -> Consonant -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Consonant -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Consonant -> m Consonant #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Consonant -> m Consonant #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Consonant -> m Consonant #

Show Consonant Source # 
Instance details

Defined in Language.IPA.Types

Generic Consonant Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Consonant :: Type -> Type #

Lift Consonant Source # 
Instance details

Defined in Language.IPA.Types

type Rep Consonant Source # 
Instance details

Defined in Language.IPA.Types

type Rep Consonant = D1 ('MetaData "Consonant" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) ((C1 ('MetaCons "Pulmonic" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phonation) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Manner))) :+: C1 ('MetaCons "Ejective" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Manner))) :+: (C1 ('MetaCons "Implosive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phonation) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place)) :+: (C1 ('MetaCons "Click" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place)) :+: C1 ('MetaCons "DoublyArticulated" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phonation) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Place) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Manner))))))

Convenience patterns

These are convenience patterns for creating different types of Consonant Segments, as the nesting of data constructors might otherwise be somewhat tiresome

Consonant features

data Manner Source #

Consonantal manner of articulation

Instances

Instances details
Eq Manner Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Manner -> Manner -> Bool #

(/=) :: Manner -> Manner -> Bool #

Data Manner Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Generic Manner Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Manner :: Type -> Type #

Methods

from :: Manner -> Rep Manner x #

to :: Rep Manner x -> Manner #

Lift Manner Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Manner -> Q Exp #

liftTyped :: Manner -> Q (TExp Manner) #

type Rep Manner Source # 
Instance details

Defined in Language.IPA.Types

type Rep Manner = D1 ('MetaData "Manner" "Language.IPA.Types" "ipa-0.3.1.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)))))

data Place Source #

Consonantal place of articulation

Instances

Instances details
Eq Place Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Place -> Place -> Bool #

(/=) :: Place -> Place -> Bool #

Data Place Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 #

toConstr :: Place -> Constr #

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 # 
Instance details

Defined in Language.IPA.Types

Methods

compare :: Place -> Place -> Ordering #

(<) :: Place -> Place -> Bool #

(<=) :: Place -> Place -> Bool #

(>) :: Place -> Place -> Bool #

(>=) :: Place -> Place -> Bool #

max :: Place -> Place -> Place #

min :: Place -> Place -> Place #

Show Place Source # 
Instance details

Defined in Language.IPA.Types

Methods

showsPrec :: Int -> Place -> ShowS #

show :: Place -> String #

showList :: [Place] -> ShowS #

Generic Place Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Place :: Type -> Type #

Methods

from :: Place -> Rep Place x #

to :: Rep Place x -> Place #

Lift Place Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Place -> Q Exp #

liftTyped :: Place -> Q (TExp Place) #

type Rep Place Source # 
Instance details

Defined in Language.IPA.Types

type Rep Place = D1 ('MetaData "Place" "Language.IPA.Types" "ipa-0.3.1.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)))))

data Phonation Source #

Phonation (voicing)

Constructors

Voiced 
Voiceless 

Instances

Instances details
Eq Phonation Source # 
Instance details

Defined in Language.IPA.Types

Data Phonation Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Generic Phonation Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Phonation :: Type -> Type #

Lift Phonation Source # 
Instance details

Defined in Language.IPA.Types

type Rep Phonation Source # 
Instance details

Defined in Language.IPA.Types

type Rep Phonation = D1 ('MetaData "Phonation" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "Voiced" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Voiceless" 'PrefixI 'False) (U1 :: Type -> Type))

data Sibilance Source #

Sibilance for fricative consonants

Constructors

Sibilant 
NonSibilant 

Instances

Instances details
Eq Sibilance Source # 
Instance details

Defined in Language.IPA.Types

Data Sibilance Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Generic Sibilance Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Sibilance :: Type -> Type #

Lift Sibilance Source # 
Instance details

Defined in Language.IPA.Types

type Rep Sibilance Source # 
Instance details

Defined in Language.IPA.Types

type Rep Sibilance = D1 ('MetaData "Sibilance" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "Sibilant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonSibilant" 'PrefixI 'False) (U1 :: Type -> Type))

Vowels

data Vowel Source #

Vowel type. Note that this type does not prevent the construction of nonsensical vowel values such as Diphthong (Diphthong ...) (Diphthong ...)

Instances

Instances details
Eq Vowel Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Vowel -> Vowel -> Bool #

(/=) :: Vowel -> Vowel -> Bool #

Data Vowel Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Vowel -> c Vowel #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Vowel #

toConstr :: Vowel -> Constr #

dataTypeOf :: Vowel -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Vowel) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Vowel) #

gmapT :: (forall b. Data b => b -> b) -> Vowel -> Vowel #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Vowel -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Vowel -> r #

gmapQ :: (forall d. Data d => d -> u) -> Vowel -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Vowel -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Vowel -> m Vowel #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Vowel -> m Vowel #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Vowel -> m Vowel #

Show Vowel Source # 
Instance details

Defined in Language.IPA.Types

Methods

showsPrec :: Int -> Vowel -> ShowS #

show :: Vowel -> String #

showList :: [Vowel] -> ShowS #

Generic Vowel Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Vowel :: Type -> Type #

Methods

from :: Vowel -> Rep Vowel x #

to :: Rep Vowel x -> Vowel #

Lift Vowel Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Vowel -> Q Exp #

liftTyped :: Vowel -> Q (TExp Vowel) #

type Rep Vowel Source # 
Instance details

Defined in Language.IPA.Types

Convenience patterns

pattern Diphthong :: Vowel -> Vowel -> Segment Source #

pattern Triphthong :: Vowel -> Vowel -> Vowel -> Segment Source #

Vowel features

data Height Source #

Vowel height

Instances

Instances details
Eq Height Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Height -> Height -> Bool #

(/=) :: Height -> Height -> Bool #

Data Height Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Generic Height Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Height :: Type -> Type #

Methods

from :: Height -> Rep Height x #

to :: Rep Height x -> Height #

Lift Height Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Height -> Q Exp #

liftTyped :: Height -> Q (TExp Height) #

type Rep Height Source # 
Instance details

Defined in Language.IPA.Types

type Rep Height = D1 ('MetaData "Height" "Language.IPA.Types" "ipa-0.3.1.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))))

data Backness Source #

Vowel backness

Constructors

Front 
NearFront 
Central 
NearBack 
Back 

Instances

Instances details
Eq Backness Source # 
Instance details

Defined in Language.IPA.Types

Data Backness Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Show Backness Source # 
Instance details

Defined in Language.IPA.Types

Generic Backness Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Backness :: Type -> Type #

Methods

from :: Backness -> Rep Backness x #

to :: Rep Backness x -> Backness #

Lift Backness Source # 
Instance details

Defined in Language.IPA.Types

type Rep Backness Source # 
Instance details

Defined in Language.IPA.Types

type Rep Backness = D1 ('MetaData "Backness" "Language.IPA.Types" "ipa-0.3.1.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

Constructors

Rounded 
Unrounded 

Instances

Instances details
Eq Roundedness Source # 
Instance details

Defined in Language.IPA.Types

Data Roundedness Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Roundedness -> c Roundedness #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Roundedness #

toConstr :: Roundedness -> Constr #

dataTypeOf :: Roundedness -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Roundedness) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Roundedness) #

gmapT :: (forall b. Data b => b -> b) -> Roundedness -> Roundedness #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Roundedness -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Roundedness -> r #

gmapQ :: (forall d. Data d => d -> u) -> Roundedness -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Roundedness -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Roundedness -> m Roundedness #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Roundedness -> m Roundedness #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Roundedness -> m Roundedness #

Show Roundedness Source # 
Instance details

Defined in Language.IPA.Types

Generic Roundedness Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Roundedness :: Type -> Type #

Lift Roundedness Source # 
Instance details

Defined in Language.IPA.Types

type Rep Roundedness Source # 
Instance details

Defined in Language.IPA.Types

type Rep Roundedness = D1 ('MetaData "Roundedness" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "Rounded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Unrounded" 'PrefixI 'False) (U1 :: Type -> Type))

Suprasegmentals

type MultiSegment t = (Applicative t, Traversable t, Monoid (t Segment)) Source #

Constraint synonym for syllable containers

data Syllable t Source #

Multiple segments, or combination of multiple segments with suprasegmental feature

Constructors

Syllable (t Segment)

A grouping of segments without extra suprasegmental information

WithSuprasegmentalFeature SuprasegmentalFeature (Syllable t)

Articulatory features that affect/encompass the entire syllable

Instances

Instances details
Lift (t Segment) => Lift (Syllable t :: Type) Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Syllable t -> Q Exp #

liftTyped :: Syllable t -> Q (TExp (Syllable t)) #

Eq (t Segment) => Eq (Syllable t) Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Syllable t -> Syllable t -> Bool #

(/=) :: Syllable t -> Syllable t -> Bool #

(Data (t Segment), Typeable t) => Data (Syllable t) Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Methods

showsPrec :: Int -> Syllable t -> ShowS #

show :: Syllable t -> String #

showList :: [Syllable t] -> ShowS #

Generic (Syllable t) Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep (Syllable t) :: Type -> Type #

Methods

from :: Syllable t -> Rep (Syllable t) x #

to :: Rep (Syllable t) x -> Syllable t #

MultiSegment t => ReprXSampa (Syllable t) Source # 
Instance details

Defined in Language.IPA.Class

MultiSegment t => ReprIPA (Syllable t) Source # 
Instance details

Defined in Language.IPA.Class

type Rep (Syllable t) Source # 
Instance details

Defined in Language.IPA.Types

Suprasegmental features

data SuprasegmentalFeature Source #

Constructors

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

Instances details
Eq SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Data SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SuprasegmentalFeature -> c SuprasegmentalFeature #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SuprasegmentalFeature #

toConstr :: SuprasegmentalFeature -> Constr #

dataTypeOf :: SuprasegmentalFeature -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SuprasegmentalFeature) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SuprasegmentalFeature) #

gmapT :: (forall b. Data b => b -> b) -> SuprasegmentalFeature -> SuprasegmentalFeature #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SuprasegmentalFeature -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SuprasegmentalFeature -> r #

gmapQ :: (forall d. Data d => d -> u) -> SuprasegmentalFeature -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SuprasegmentalFeature -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SuprasegmentalFeature -> m SuprasegmentalFeature #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SuprasegmentalFeature -> m SuprasegmentalFeature #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SuprasegmentalFeature -> m SuprasegmentalFeature #

Show SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Generic SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep SuprasegmentalFeature :: Type -> Type #

Lift SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

type Rep SuprasegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

data ToneContour Source #

Lexical tone represented as a contour

Instances

Instances details
Eq ToneContour Source # 
Instance details

Defined in Language.IPA.Types

Data ToneContour Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ToneContour -> c ToneContour #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ToneContour #

toConstr :: ToneContour -> Constr #

dataTypeOf :: ToneContour -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ToneContour) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ToneContour) #

gmapT :: (forall b. Data b => b -> b) -> ToneContour -> ToneContour #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ToneContour -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ToneContour -> r #

gmapQ :: (forall d. Data d => d -> u) -> ToneContour -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ToneContour -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ToneContour -> m ToneContour #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ToneContour -> m ToneContour #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ToneContour -> m ToneContour #

Ord ToneContour Source # 
Instance details

Defined in Language.IPA.Types

Show ToneContour Source # 
Instance details

Defined in Language.IPA.Types

Generic ToneContour Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep ToneContour :: Type -> Type #

Lift ToneContour Source # 
Instance details

Defined in Language.IPA.Types

type Rep ToneContour Source # 
Instance details

Defined in Language.IPA.Types

type Rep ToneContour = D1 ('MetaData "ToneContour" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (((C1 ('MetaCons "Rising" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Falling" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "HighRising" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LowRising" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HighFalling" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LowFalling" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RisingFalling" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FallingRising" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GlobalRise" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GlobalFall" 'PrefixI 'False) (U1 :: Type -> Type)))))

data LevelTone Source #

Lexical tone with Chao-style tone letters

Instances

Instances details
Eq LevelTone Source # 
Instance details

Defined in Language.IPA.Types

Data LevelTone Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Show LevelTone Source # 
Instance details

Defined in Language.IPA.Types

Generic LevelTone Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep LevelTone :: Type -> Type #

Lift LevelTone Source # 
Instance details

Defined in Language.IPA.Types

type Rep LevelTone Source # 
Instance details

Defined in Language.IPA.Types

type Rep LevelTone = D1 ('MetaData "LevelTone" "Language.IPA.Types" "ipa-0.3.1.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))))

data Stress Source #

Constructors

Primary 
Secondary 

Instances

Instances details
Eq Stress Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Stress -> Stress -> Bool #

(/=) :: Stress -> Stress -> Bool #

Data Stress Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Show Stress Source # 
Instance details

Defined in Language.IPA.Types

Generic Stress Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Stress :: Type -> Type #

Methods

from :: Stress -> Rep Stress x #

to :: Rep Stress x -> Stress #

Lift Stress Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Stress -> Q Exp #

liftTyped :: Stress -> Q (TExp Stress) #

type Rep Stress Source # 
Instance details

Defined in Language.IPA.Types

type Rep Stress = D1 ('MetaData "Stress" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "Primary" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Secondary" 'PrefixI 'False) (U1 :: Type -> Type))

Segmental articulatory features

data Length Source #

Vowel length; also serves as a notation for consonant gemination in the IPA

Constructors

OverLong 
HalfLong 
Long 
Short

The default/unmarked length; using this constructor doesn't affect the default IPA representation of the segment

ExtraShort 

Instances

Instances details
Eq Length Source # 
Instance details

Defined in Language.IPA.Types

Methods

(==) :: Length -> Length -> Bool #

(/=) :: Length -> Length -> Bool #

Data Length Source # 
Instance details

Defined in Language.IPA.Types

Methods

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 # 
Instance details

Defined in Language.IPA.Types

Show Length Source # 
Instance details

Defined in Language.IPA.Types

Generic Length Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Length :: Type -> Type #

Methods

from :: Length -> Rep Length x #

to :: Rep Length x -> Length #

Lift Length Source # 
Instance details

Defined in Language.IPA.Types

Methods

lift :: Length -> Q Exp #

liftTyped :: Length -> Q (TExp Length) #

type Rep Length Source # 
Instance details

Defined in Language.IPA.Types

type Rep Length = D1 ('MetaData "Length" "Language.IPA.Types" "ipa-0.3.1.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 Segments 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

Instances details
Eq SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Data SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegmentalFeature -> c SegmentalFeature #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegmentalFeature #

toConstr :: SegmentalFeature -> Constr #

dataTypeOf :: SegmentalFeature -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SegmentalFeature) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegmentalFeature) #

gmapT :: (forall b. Data b => b -> b) -> SegmentalFeature -> SegmentalFeature #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegmentalFeature -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegmentalFeature -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegmentalFeature -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegmentalFeature -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegmentalFeature -> m SegmentalFeature #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentalFeature -> m SegmentalFeature #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegmentalFeature -> m SegmentalFeature #

Show SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Generic SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep SegmentalFeature :: Type -> Type #

Lift SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

type Rep SegmentalFeature Source # 
Instance details

Defined in Language.IPA.Types

type Rep SegmentalFeature = D1 ('MetaData "SegmentalFeature" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (((((C1 ('MetaCons "Voicing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Phonation)) :+: C1 ('MetaCons "Length" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Length))) :+: (C1 ('MetaCons "SecondaryArticulation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Segment)) :+: C1 ('MetaCons "Aspirated" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MoreRounded" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LessRounded" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Advanced" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Retracted" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Centralized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MidCentralized" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Compressed" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Syllabic" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NonSyllabic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rhotacized" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BreathyVoice" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CreakyVoice" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "LinguoLabialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Labialized" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Palatalized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Velarized" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Pharyngealized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Raised" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Lowered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AdvancedTongueRoot" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "RetractedTongueRoot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dentalized" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Apical" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Laminal" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Nasalized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NasalRelease" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LateralRelease" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoAudibleRelease" 'PrefixI 'False) (U1 :: Type -> Type))))))

Transcription delimiters

data Delimiter Source #

Transcription delimiters/brackets

Constructors

Phonetic

Actual pronunciation, transcribed with square brackets, [ .. ]

Phonemic

Abstract phonemic representation, transcribed with slashes, / .. /

Instances

Instances details
Eq Delimiter Source # 
Instance details

Defined in Language.IPA.Types

Show Delimiter Source # 
Instance details

Defined in Language.IPA.Types

Generic Delimiter Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep Delimiter :: Type -> Type #

type Rep Delimiter Source # 
Instance details

Defined in Language.IPA.Types

type Rep Delimiter = D1 ('MetaData "Delimiter" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "Phonetic" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Phonemic" 'PrefixI 'False) (U1 :: Type -> Type))

Errors

data IPAException Source #

Instances

Instances details
Eq IPAException Source # 
Instance details

Defined in Language.IPA.Types

Show IPAException Source # 
Instance details

Defined in Language.IPA.Types

Generic IPAException Source # 
Instance details

Defined in Language.IPA.Types

Associated Types

type Rep IPAException :: Type -> Type #

Exception IPAException Source # 
Instance details

Defined in Language.IPA.Types

type Rep IPAException Source # 
Instance details

Defined in Language.IPA.Types

type Rep IPAException = D1 ('MetaData "IPAException" "Language.IPA.Types" "ipa-0.3.1.1-inplace" 'False) (C1 ('MetaCons "InvalidIPA" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "InvalidXSampa" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))