add script to lántas pages

This commit is contained in:
Rhiannon Morris 2021-04-29 11:55:54 +02:00
parent ba5522187c
commit f61e5b1146
13 changed files with 332 additions and 143 deletions

View File

@ -2,11 +2,11 @@
module Glyphs
(Glyph (..), Segs (..), Piece, doGlyphs,
withSize, size,
withSize,
charHeight', lineHeight', spaceWidth', gap',
charHeight, lineHeight, spaceWidth, gap,
initials, finals, vowels, medials, num, numbers, punctuation)
initials, finals, vowels, medials, num, numbers, punctuation, wave)
where
import Data.Map (Map)
@ -668,3 +668,7 @@ n4Path = P [mA (1.5,0), lR (0,5), sR (-1.5,-3) (-1.5,-5), lR (5,0), lR (0,5)]
n5 = G n5Path 4
n5Path = P [mA (0,0), lR (0,3.5), aR 1.5 1.5 0 Small CCW (1.5,1.5),
lR (1,0), aR 1.5 1.5 0 Small CCW (1.5,-1.5), lR (0,-3.5)]
wave :: Glyph
wave = G {path = wavePath, width = 4} where
wavePath = P [mA (0,2.5), cR (1.5,-2) (2.5,2) (4,0)]

View File

@ -21,9 +21,6 @@ gap' = 1.5
withSize :: MonadReader Env m => (Double -> a) -> m a
withSize f = asks \E {size} -> f size
size :: MonadReader Env m => m Double
size = withSize id
-- | multiplied by size
charHeight, lineHeight, spaceWidth, margin, gap :: MonadReader Env m => m Double
charHeight = withSize (* charHeight')
@ -34,7 +31,15 @@ gap = withSize (* gap')
data Segs = P [M Text] | Shift !Double !Double Segs | Segs :<>: Segs
instance Semigroup Segs where (<>) = (:<>:)
instance Semigroup Segs where
P [] <> s = s
s <> P [] = s
P ss <> P ts = P $ ss <> ts
s <> t = s :<>: t
instance Monoid Segs where
mempty = P []
mappend = (<>)
joinSegs :: Segs -> M Text
joinSegs (P ps) = fmap mconcat $ sequence ps
@ -74,8 +79,8 @@ type Word = [EGlyph]
doGlyphs :: [Word] -> Env -> Element
doGlyphs gs e = wrap $ run act e where
act = do
E {stroke} <- ask
let gattrs = [Stroke_ <<- "black", Stroke_width_ <<- toPx stroke,
E {stroke, color} <- ask
let gattrs = [Stroke_ <<- color, Stroke_width_ <<- toPx stroke,
Stroke_linecap_ <<- "round", Fill_ <<- "none"]
g_ gattrs . mconcat <$> traverse placeWord gs <* newline
wrap (content, T {width, height}) =

View File

@ -1,5 +1,3 @@
{-# OPTIONS_GHC -fdefer-typed-holes #-}
import Prelude hiding (getContents, readFile, writeFile, putStrLn)
import Svg
import Glyphs (doGlyphs, lineHeight')
@ -13,8 +11,9 @@ import Data.Text.Lazy.IO (writeFile, putStrLn)
data Options =
Opts {
width, size, stroke :: {-# UNPACK #-} !Double,
inFile, outFile :: Maybe FilePath,
text :: Maybe Text
inFile, outFile :: Maybe FilePath,
text :: Maybe Text,
color :: Text
}
deriving Show
@ -29,6 +28,7 @@ options = execParser desc where
<*> filePath 'i' "input"
<*> filePath 'o' "output"
<*> text
<*> color
dimOpt s l d = dimOpt' s l l d
dimOpt' s l n d = option auto $ mconcat
[short s, long l, help $ n <> " in pixels", metavar "SIZE", value d]
@ -37,6 +37,9 @@ options = execParser desc where
text = optional $ option str $ mconcat
[short 't', long "text", help $ "use given text instead of a file",
metavar "TEXT"]
color = option str $ mconcat
[short 'C', long "color", help $ "set stroke color (any css syntax)",
metavar "COLOR", value "black"]
main :: IO ()
main = do

View File

@ -1,5 +1,3 @@
{-# OPTIONS_GHC -fdefer-typed-holes #-}
module Split (split) where
import Glyphs
@ -16,11 +14,14 @@ import Data.Void
type P = Parsec Void Text
lcChar :: P Char
lcChar = Char.toLower <$> anySingle
longestWith :: String -> (Text -> Maybe a) -> P a
longestWith name p = try $ go . Text.singleton =<< anySingle where
longestWith name p = try $ go . Text.singleton =<< lcChar where
go acc = case p acc of
Nothing -> fail $ "longestWith " <> name <> ": " <> show acc
Just x -> try (do c <- anySingle; go $ Text.snoc acc c) <|> pure x
Just x -> try (do c <- lcChar; go $ Text.snoc acc c) <|> pure x
maxFrom :: String -> Map Text a -> P a
maxFrom name i = longestWith name \x -> Map.lookup x i
@ -29,7 +30,7 @@ initial :: P Glyph
initial = maxFrom "initial" initials
medial :: P Segs
medial = maxFrom "medial" medials
medial = P [] <$ chunk "\\" <|> maxFrom "medial" medials
final :: P Glyph
final = maxFrom "final" finals
@ -40,18 +41,22 @@ ivowel = maxFrom "vowel" vowels
word :: P [Piece]
word = (<>) <$> some initMed <*> fin where
initMed = try $
[(i, ms) | i <- initial, ms <- some medial] <|>
[(v, []) | v <- ivowel]
[(i, [m]) | i <- initial, m <- medial] <|>
[(v, []) | v <- ivowel] <|>
dash
fin = maybe [] (\x -> [(x, [])]) <$> optional final
number :: P [Piece]
number = [[h1] <> ns <> [h2] | h1 <- hash, ns <- some digit, h2 <- hash] where
number = some (digit <|> hash) where
hash = (num, []) <$ chunk "#"
digit = [(numbers ! Char.digitToInt i, []) | i <- digitChar]
punct :: P [Piece]
punct = [[(p, [])] | p <- maxFrom "punctuation" punctuation]
dash :: P Piece
dash = (wave, []) <$ chunk ""
text :: P [[Piece]]
text = space *> many (segment <* space) <* eof where
segment = punct <|> number <|> word

View File

@ -13,7 +13,7 @@ import Graphics.Svg hiding (mA, mR, lA, lR, cA, cR, sA, sR, aA, aR)
import Data.Text (Text, pack)
data Env = E {width, size, stroke :: !Double}
data Env = E {width, size, stroke :: !Double, color :: !Text}
data St = S {x, y, textWidth, textHeight :: !Double}
-- nb textHeight is one lineheight less than the actual height
-- unless ending with a 'newline'

View File

@ -3,6 +3,7 @@ title: List of abbreviations
hidetoc: true
backname: Lántas
backlink: ../laantas
lang: lántas
...
:::threecol

View File

@ -1,10 +1,15 @@
---
title: Lántas
toc: false
lang: lántas
...
:::splash
`{#lántas | size = 200 ; stroke = 7}`
:::
1. [Phonology](phono.html)
2. [Writing system] need to extract from the old mess
2. [Writing system](writing.html)
3. [Nouns](nouns.html)
4. [Pronouns, etc](prons.html)
5. [Verbs](verbs.html)

View File

@ -2,6 +2,7 @@
title: Lántas nouns
backname: Lántas
backlink: .
lang: lántas
...
Lántas is unusual (as far as I know) in that words which are often considered
@ -13,9 +14,9 @@ genitive case of) nouns.
The basic form of a noun is its singular, in all cases. The plural is formed by adding:
- `{-al}` to a word ending in `{l}` or `{ł}`,
- `{-l}` to a word ending in a vowel, or
- `{-ł}` to a word ending in a consonant, syllabic or not, other than `{l}`.
- `{!al}` to a word ending in `{l}` or `{ł}`,
- `{!l}` to a word ending in a vowel, or
- `{!ł}` to a word ending in a consonant, syllabic or not, other than `{l}`.
This plural form can also be applied to names of people. In this case it forms
what is called an _associative plural_, and refers to a person plus a group
@ -38,26 +39,26 @@ associated with them, usually their family or friend group.
# Definiteness
The definite suffix for nouns `!(DEF)!` is usually `{-m}`, and is used more
The definite suffix for nouns `!(DEF)!` is usually `{!m}`, and is used more
frequently than 'the' in English. For example, in the first sentence below Sam
has one dog, but in the second he is implied to have several. The names of
people and places are also definite.
The suffix has a few different forms depending on how the word ends:
Ending Suffix Examples
------------------------- --------- --------------------------------
`{m}` or `{ḿ}` `{-am}` `{šaksḿ}` 'the ash',
**TODO word ending in m**
other consonant or `{ń}` `{-ḿ}` `{lántasḿ}` 'the language',
`{kášńḿ}` 'the lizard'
vowel, `{ŕ}`, or `{ł}` `{-m}` `{luwam}` 'the truth',
`{laksŕm}` 'the fish',
`{ustaiƶłm}` 'the singer'
------------------------- --------- --------------------------------
Ending Suffix Examples
------------------------- ---------- --------------------------------
`{m}` or `{ḿ}` `{!am}` `{!šaksḿam}` 'the ash',
**TODO word ending in m**
other consonant or `{ń}` `{!–ḿ}` `{!lántasḿ}` 'the language',
`{!kášńḿ}` 'the lizard'
vowel, `{ŕ}`, or `{ł}` `{!m}` `{!luwam}` 'the truth',
`{!laksŕm}` 'the fish',
`{!ustaiƶłm}` 'the singer'
------------------------- ---------- --------------------------------
A sequence `{ńḿ}` formed in this way is pronounced as `/nm̩/`. In other words,
`{kášńḿ}` has *two* syllables, not three like it is written. An extra `{-a}` is
`{!kášńḿ}` has *two* syllables, not three like it is written. An extra `{-a}` is
inserted after the `{-m}` form of the suffix if it is needed due to another
suffix following it.
@ -87,65 +88,73 @@ suffix following it.
The definite suffix is used:
:::examples
- When the referent is old information already mentioned.
- `{Pas nú bairusina. Nai rala núm manifnut gašnat ippausi.}`\
- `{!Pas nú bairusina.}` \
`{!Nai rala núm manifnut gašnat ippausi.}` \
I saw two people. One of them was wearing a nice shirt.
- For people, places, countries, and other proper names.
- `{Ƶuƶ pas kášńł ǧiššimamba nuabia.}`\
- `{!Ƶuƶ pas kášńł ǧiššimamba nuabia.}`\
Those two lizards live above the bakery.
- In time phrases with `{gimi}`. However, `{naigimi}` 'sometime' is indefinite.
- `{Gimimli lána.}`\
- In time phrases with `{!gimi}`. However, `{!naigimi}` 'sometime' is indefinite.
- `{!Gimimli lána.}`\
I'm doing it now.
- `{Naigimimli lámána.}`\
- `{!Naigimimli lámána.}`\
I'll do it at some point.
- In statements of general fact.
- `{Númsal pasla aƶal ai.}`\
- `{!Númsal pasla aƶal ai.}`\
Humans have two eyes.
- __TODO: ?__
:::
The definite suffix is _not_ used (in contrast to English):
:::examples
- In superlatives.
- `{Milnutlit aifa.}`\
- `{!Milnutlit aifa.}`\
It's the smallest.
- __TODO: ?__
:::
# Core cases {#corecases}
Declension for the core cases of `{nú}` 'man' and `{lun}` 'road' are shown
Declension for the core cases of `{!nú}` 'man' and `{!lun}` 'road' are shown
below. Some of the endings are slightly different in the case of a stem ending
in a consonant or vowel, and if the ending starts with multiple consonants the
final one of the stem is dropped.
:::figure
  `!SG!` `!PL!`
----------------------- ----------- -------------
Nominative `!(NOM)!` `{nú}` `{nú·l}`
Genitive `!(GEN)!` `{nú·t}` `{nú·t·ł}`
Comitative `!(COM)!` `{nú·kas}` `{nú·kas·ł}`
Caritive `!(CAR)!` `{nú·ssa}` `{nú·ssa·l}`
Instrumental `!(INS)!` `{nú·la}` `{nú·la·l}`
Essive `!(ESS)!` `{nú·gu}` `{nú·gu·l}`
Translative `!(TRA)!` `{nú·sti}` `{nú·sti·l}`
Exessive `!(EXE)!` `{nú·ču}` `{nú·ču·l}`
  `!SG !` `!PL!`
----------------------- ------------ --------------
Nominative `!(NOM)!` `{!nú}` `{!nú·l}`
Genitive `!(GEN)!` `{!nú·t}` `{!nú·t·ł}`
Comitative `!(COM)!` `{!nú·kas}` `{!nú·kas·ł}`
Caritive `!(CAR)!` `{!nú·ssa}` `{!nú·ssa·l}`
Instrumental `!(INS)!` `{!nú·la}` `{!nú·la·l}`
Essive `!(ESS)!` `{!nú·gu}` `{!nú·gu·l}`
Translative `!(TRA)!` `{!nú·sti}` `{!nú·sti·l}`
Exessive `!(EXE)!` `{!nú·ču}` `{!nú·ču·l}`
  `!SG!` `!PL!`
-------- ----------- --------------
`!NOM!` `{lun}` `{lun·ł}`
`!GEN!` `{lu·t}` `{lun·t·ł}`
`!COM!` `{lun·kas}` `{lun·kas·ł}`
`!CAR!` `{lu·ssa}` `{lu·ssa·l}`
`!INS!` `{lun·la}` `{lun·la·l}`
`!ESS!` `{lun·gu}` `{lun·gu·l}`
`!TRA!` `{lu·sti}` `{lu·sti·l}`
`!EXE!` `{lun·ču}` `{lun·ču·l}`
  `!SG!` `!PL!`
-------- ------------ ---------------
`!NOM!` `{!lun}` `{!lun·ł}`
`!GEN!` `{!lu·t}` `{!lun·t·ł}`
`!COM!` `{!lun·kas}` `{!lun·kas·ł}`
`!CAR!` `{!lu·ssa}` `{!lu·ssa·l}`
`!INS!` `{!lun·la}` `{!lun·la·l}`
`!ESS!` `{!lun·gu}` `{!lun·gu·l}`
`!TRA!` `{!lu·sti}` `{!lu·sti·l}`
`!EXE!` `{!lun·ču}` `{!lun·ču·l}`
:::
The _nominative_ is the subject of sentences, and the unmarked form. The
@ -221,7 +230,7 @@ affirmative statements.)
The most common use of the _instrumental_ case is the "[theme]" of ditransitive
sentences (while the recipient is in the genitive). It is also used for 'with'
as in 'using', in distributive phrases such as `{kallila}` 'in threes, in sets
as in 'using', in distributive phrases such as `{!kallila}` 'in threes, in sets
of three, three each', for quantity expressions such as units, and quantifiers
like 'every'.
@ -312,48 +321,48 @@ indicate the relative position:
:::
Unlike for the core cases, the endings are the same regardless of whether the
stem ends in a consonant or vowel, so they are only listed for `{nú}`.
stem ends in a consonant or vowel, so they are only listed for `{!nú}`.
:::figure
    `!ESS!` `!LAT!` `!ABL!` `!PRL!`
---------- ------- ------------- --------------- --------------- ----------------
`!AD!` `!SG!` `{nú·sa}` `{nú·sa·s}` `{nú·sa·n}` `{nú·sa·ri}`
`!PL!` `{nú·sa·l}` `{nú·sa·s·ł}` `{nú·sa·n·ł}` `{nú·sa·ri·l}`
`!IN!` `!SG!` `{nú·li}` `{nú·li·s}` `{nú·li·n}` `{nú·li·ri}`
`!PL!` `{nú·li·l}` `{nú·li·s·ł}` `{nú·li·n·ł}` `{nú·li·ri·l}`
`!PRE!` `!SG!` `{nú·ƶu}` `{nú·ƶu·s}` `{nú·ƶu·n}` `{nú·ƶu·ri}`
`!PL!` `{nú·ƶu·l}` `{nú·ƶu·s·ł}` `{nú·ƶu·n·ł}` `{nú·ƶu·ri·l}`
`!POST!` `!SG!` `{nú·gi}` `{nú·gi·s}` `{nú·gi·n}` `{nú·gi·ri}`
`!PL!` `{nú·gi·l}` `{nú·gi·s·ł}` `{nú·gi·n·ł}` `{nú·gi·ri·l}`
`!INTER!` `!SG!` `{nú·nua}` `{nú·nua·s}` `{nú·nua·n}` `{nú·nua·ri}`
`!PL!` `{nú·nua·l}` `{nú·nua·s·ł}` `{nú·nua·n·ł}` `{nú·nua·ri·l}`
`!SUPER!` `!SG!` `{nú·ba}` `{nú·ba·s}` `{nú·ba·n}` `{nú·ba·ri}`
`!PL!` `{nú·ba·l}` `{nú·ba·s·ł}` `{nú·ba·n·ł}` `{nú·ba·ri·l}`
`!SUB!` `!SG!` `{nú·ku}` `{nú·ku·s}` `{nú·ku·n}` `{nú·ku·ri}`
`!PL!` `{nú·ku·l}` `{nú·ku·s·ł}` `{nú·ku·n·ł}` `{nú·ku·ri·l}`
`!APUD!` `!SG!` `{nú·mi}` `{nú·mi·s}` `{nú·mi·n}` `{nú·mi·ri}`
`!PL!` `{nú·mi·l}` `{nú·mi·s·ł}` `{nú·mi·n·ł}` `{nú·mi·ri·l}`
    `!ESS!` `!LAT!` `!ABL!` `!PRL!`
---------- ------- -------------- ---------------- ---------------- -----------------
`!AD!` `!SG!` `{!nú·sa}` `{!nú·sa·s}` `{!nú·sa·n}` `{!nú·sa·ri}`
`!PL!` `{!nú·sa·l}` `{!nú·sa·s·ł}` `{!nú·sa·n·ł}` `{!nú·sa·ri·l}`
`!IN!` `!SG!` `{!nú·li}` `{!nú·li·s}` `{!nú·li·n}` `{!nú·li·ri}`
`!PL!` `{!nú·li·l}` `{!nú·li·s·ł}` `{!nú·li·n·ł}` `{!nú·li·ri·l}`
`!PRE!` `!SG!` `{!nú·ƶu}` `{!nú·ƶu·s}` `{!nú·ƶu·n}` `{!nú·ƶu·ri}`
`!PL!` `{!nú·ƶu·l}` `{!nú·ƶu·s·ł}` `{!nú·ƶu·n·ł}` `{!nú·ƶu·ri·l}`
`!POST!` `!SG!` `{!nú·gi}` `{!nú·gi·s}` `{!nú·gi·n}` `{!nú·gi·ri}`
`!PL!` `{!nú·gi·l}` `{!nú·gi·s·ł}` `{!nú·gi·n·ł}` `{!nú·gi·ri·l}`
`!INTER!` `!SG!` `{!nú·nua}` `{!nú·nua·s}` `{!nú·nua·n}` `{!nú·nua·ri}`
`!PL!` `{!nú·nua·l}` `{!nú·nua·s·ł}` `{!nú·nua·n·ł}` `{!nú·nua·ri·l}`
`!SUPER!` `!SG!` `{!nú·ba}` `{!nú·ba·s}` `{!nú·ba·n}` `{!nú·ba·ri}`
`!PL!` `{!nú·ba·l}` `{!nú·ba·s·ł}` `{!nú·ba·n·ł}` `{!nú·ba·ri·l}`
`!SUB!` `!SG!` `{!nú·ku}` `{!nú·ku·s}` `{!nú·ku·n}` `{!nú·ku·ri}`
`!PL!` `{!nú·ku·l}` `{!nú·ku·s·ł}` `{!nú·ku·n·ł}` `{!nú·ku·ri·l}`
`!APUD!` `!SG!` `{!nú·mi}` `{!nú·mi·s}` `{!nú·mi·n}` `{!nú·mi·ri}`
`!PL!` `{!nú·mi·l}` `{!nú·mi·s·ł}` `{!nú·mi·n·ł}` `{!nú·mi·ri·l}`
:::
:::figure
- `{Dufnamsas júlisina.}`\
- `{!Dufnamsas júlisina.}`\
`!(AD-LAT)!` I stuck it onto the wall.
- `{Ǧimamsa aihapa?}`\
- `{!Ǧimamsa aihapa?}`\
`!(AD-ESS)!` Are you at home?
- `{Sihamgit ǧimamlis šikkúmána.}`\
- `{!Sihamgit ǧimamlis šikkúmána.}`\
`!(IN-LAT)!` I'll be going home soon.
- `{Sabut kalń káƶuri narasi.}`\
- `{!Sabut kalń káƶuri narasi.}`\
`!(PRE-PRL)!` A black cat passed in front of me.
- `{Ǧimamgi waibifás.}`\
- `{!Ǧimamgi waibifás.}`\
`!(POST-ESS)!` They're playing round the back of the house.
- `{Lunsari šikkúsina.}`\
- `{!Lunsari šikkúsina.}`\
`!(AD-PRL)!` I went down the road.
- `{Lunliri šikkúsina.}`\
- `{!Lunliri šikkúsina.}`\
`!(IN-PRL)!` I went across the road.
- `{Lunmiri šikkúsina.}`\
- `{!Lunmiri šikkúsina.}`\
`!(APUD-PRL)!` I followed (alongside) the river.
:::
@ -424,17 +433,23 @@ variant is `{-ttás}`.
- The mouse is squeaking quietly.
:::
From adjectivals, several further derivations can be made: the _equative_, which expresses that two objects have an equal measure of some property; the _comparative_, which says that one object has more of a property than another object; and the _superlative_, which claims that an object has the most of a property. Derivation from `{gaisi}` 'white':
From adjectivals, several further derivations can be made: the _equative_,
which expresses that two objects have an equal measure of some property; the
_comparative_, which says that one object has more of a property than another
object; and the _superlative_, which claims that an object has the most of
a property.
:::figure
----------------------- ---------------
Equative `!(EQU)!` `{gaisi·t·sat}`
Comparative `!(CMP)!` `{gaisi·t·pat}`
Superlative `!(SUPL)!` `{gaisi·t·lit}`
----------------------- ---------------
----------------------- ---------------- ------------
Adjective `{!ausu·t}` big
Equative `!(EQU)!` `{!ausu·t·sat}` as big as
Comparative `!(CMP)!` `{!ausu·t·pat}` bigger than
Superlative `!(SUPL)!` `{!ausu·t·lit}` the biggest
----------------------- ---------------- ------------
:::
The noun being compared with is in the [essive case](#corecases) for the equative, and the exessive for the comparative.
The noun being compared with is in the [essive case](#corecases) for the
equative, and the exessive for the comparative.
:::glosses
- ǧimagu ausutsat

View File

@ -2,22 +2,32 @@
title: Lántas numbers
hidetoc: true
backname: Lántas
backlink: ../laantas
backlink: .
lang: lántas
...
--- ------------ ---- ----------------- ---- --------------- ------ -----------------
1 `{nai}` 10 `{taksa}` 19 `{taksístu}` 100 `{bušŕ}`
2 `{pas}` 11 `{tahnai}` 20 `{pastaksa}` 1000 `{nifma}`
3 `{kalli}` 12 `{tappas}` 30 `{kaldaksa}` 10⁴ `{hárual}`
4 `{šasḿ}` 13 `{takkalli}` 40 `{šastaksa}` 10⁵ `{taksahárual}`
5 `{kaisi}` 14 `{taksasḿ}` 50 `{kaistaksa}` 10⁶ `{bušŕhárual}`
6 `{ǧutta}` 15 `{takkaisi}` 60 `{ǧuttaksa}` 10⁷ `{nifmahárual}`
7 `{libina}` 16 `{taččutta}` 70 `{libidaksa}` 10⁸ `{kḿpsi}`
8 `{ńdá}` 17 `{taksalibina}` 80 `{ńtaksa}` 10¹² `{kahmil}`
9 `{ístu}` 18 `{taksandá}` 90 `{ístaksa}` 10¹⁶ `{uhnat}`
--- ------------ ---- ----------------- ---- --------------- ------ -----------------
---- ------------------ ------ ------------------
1 `{!nai}` 19 `{!taksístu}`
2 `{!pas}` 20 `{!pastaksa}`
3 `{!kalli}` 30 `{!kaldaksa}`
4 `{!šasḿ}` 40 `{!šastaksa}`
5 `{!kaisi}` 50 `{!kaistaksa}`
6 `{!ǧutta}` 60 `{!ǧuttaksa}`
7 `{!libina}` 70 `{!libidaksa}`
8 `{!ńdá}` 80 `{!ńtaksa}`
9 `{!ístu}` 90 `{!ístaksa}`
10 `{!taksa}` 100 `{!bušŕ}`
11 `{!tahnai}` 1000 `{!nifma}`
12 `{!tappas}` 10⁴ `{!hárual}`
13 `{!takkalli}` 10⁵ `{!taksahárual}`
14 `{!taksasḿ}` 10⁶ `{!bušŕhárual}`
15 `{!takkaisi}` 10⁷ `{!nifmahárual}`
16 `{!taččutta}` 10⁸ `{!kḿpsi}`
17 `{!taksalibina}` 10¹² `{!kahmil}`
18 `{!taksandá}` 10¹⁶ `{!uhnat}`
---- ------------------ ------ ------------------
Numbers between 20--99 are formed by analogy with those from 11--19, for example
`{kaldappas}` for 32 or `{ǧuttaččutta}` for 66. Numbers are given from largest
`{!kaldappas}` for 32 or `{!ǧuttaččutta}` for 66. Numbers are given from largest
to smallest, with the value and place of each digit written as one word, so
43,523 is `{šasḿhárual kallinifma kaisibušŕ pastakkalli}`.
43,523 is `{!šasḿhárual kallinifma kaisibušŕ pastakkalli}`.

View File

@ -2,6 +2,7 @@
title: Lántas phonology
backname: Lántas
backlink: .
lang: lántas
...
# Vowels
@ -31,7 +32,7 @@ acute with a stroke: `{ł}`. The diphthongs are spelt `{ai au ia ua}`.
* After `/tʃ dʒ ʃ j/`, `/u uː/` is fronted to `[y ʉː]`.
* Before a syllabic consonant, a small schwa may be inserted if necessary to
make pronunciation easier. This is most common between `/ln̩ nl̩/` and two copies
of a single sound. For example, `{kalń}` 'cat': `/kaln̩/``[kɐlᵊn]`.
of a single sound. For example, `{!kalń}` 'cat': `/kaln̩/``[kɐlᵊn]`.
* `/r̩ l̩/` are pronounced as `[ɻː ɫ̩ː]`.
* Syllabic `/n̩/` assimilates to `[ŋ̍]` before a velar consonant; no other
assimilation for syllabic nasals occurs, though. (It does for *non*-syllabic
@ -66,7 +67,7 @@ In places I have forgotten to update, `/θ/` might be written `{þ}` or `{ð}`.
- Before `/i iː iə/`, `/ɾ/` becomes `[ʑ̞]`.
- A nasal followed by a plosive assimilates to the same place of articulation
(but for compound words this is not reflected in the spelling), for example
`{rabanpa}` `[ravampa]` 'what book?'.
`{!rabanpa}` `[ravampa]` 'what book?'.
- The sequences `/tʃs/` is pronounced as `[tʃː]`, and `/ʃs sʃ ʃj sj/` are all
`[ʃː]`.
- Nasals before `/s x/` decay to a nasalisation of the previous vowel, or are

View File

@ -2,6 +2,7 @@
title: Lántas pronouns, demonstratives, etc
backname: Lántas
backlink: .
lang: lántas
...
Pronouns are inflected for the same cases as other nouns, though their forms
@ -10,8 +11,8 @@ are somewhat irregular.
# Personal pronouns
The first person plural `{til}` is only used inclusively of the listener. For an
exclusive meaning, a form like `{rukas ká}` ('they and I') is used.
The first person plural `{!til}` is only used inclusively of the listener. For an
exclusive meaning, a form like `{!rukas ká}` ('they and I') is used.
The `!LOC!` column is the word stems which the [locational
cases](#locational_cases) are attached to. Their suffixes are regular.
@ -19,17 +20,17 @@ cases](#locational_cases) are attached to. Their suffixes are regular.
:::figure
`!1SG!` `!1PL!` `!2SG!` `!2PL!` `!3SG!` `!3PL!`
-------- ----------- ------------ ----------- ------------ ----------- ------------
`!NOM!` `{ká}` `{til}` `{sur}` `{sual}` `{rú}` `{rúl}`
`!GEN!` `{kat}` `{tial}` `{sut}` `{suatł}` `{rut}` `{rutł}`
`!COM!` `{kakas}` `{tiksł}` `{sukas}` `{suksł}` `{rukas}` `{ruksł}`
`!CAR!` `{kassa}` `{tissal}` `{sussa}` `{sussal}` `{russa}` `{russal}`
`!INS!` `{kala}` `{tilla}` `{sulla}` `{sualla}` `{rulla}` `{rualla}`
`!ESS!` `{kagu}` `{tigul}` `{sugu}` `{sugul}` `{rugu}` `{rugul}`
`!TRA!` `{kasti}` `{tistil}` `{susti}` `{sustul}` `{rusti}` `{rustil}`
`!EXE!` `{kaču}` `{tičul}` `{sučču}` `{suččul}` `{ruču}` `{ručul}`
`!LOC!` `{}` `{l}` `{}` `{sual}` `{}` `{rual}`
`!1SG!` `!1PL!` `!2SG!` `!2PL!` `!3SG!` `!3PL!`
-------- ------------ ------------- ------------ ------------- ------------ ------------
`!NOM!` `{!ká}` `{!til}` `{!sur}` `{!sual}` `{!rú}` `{!rúl}`
`!GEN!` `{!kat}` `{!tial}` `{!sut}` `{!suatł}` `{!rut}` `{!rutł}`
`!COM!` `{!kakas}` `{!tiksł}` `{!sukas}` `{!suksł}` `{!rukas}` `{!ruksł}`
`!CAR!` `{!kassa}` `{!tissal}` `{!sussa}` `{!sussal}` `{!russa}` `{!russal}`
`!INS!` `{!kala}` `{!tilla}` `{!sulla}` `{!sualla}` `{!rulla}` `{!rualla}`
`!ESS!` `{!kagu}` `{!tigul}` `{!sugu}` `{!sugul}` `{!rugu}` `{!rugul}`
`!TRA!` `{!kasti}` `{!tistil}` `{!susti}` `{!sustul}` `{!rusti}` `{!rustil}`
`!EXE!` `{!kaču}` `{!tičul}` `{!sučču}` `{!suččul}` `{!ruču}` `{!ručul}`
`!LOC!` `{!}` `{!l}` `{!}` `{!sual}` `{!}` `{!rual}`
:::
@ -37,24 +38,24 @@ cases](#locational_cases) are attached to. Their suffixes are regular.
There is a three way distance distinction for demonstratives: a new referent near the speaker/listener, a new referent distant from both, and old information. These will be glossed as 'this', 'yon', and 'that', respectively.
The near demonstrative is `{lua}`, whose declension is given below. For distant referents it is `{ƶua}` and for old information `{mua}`; they decline in the same way as `{lua}`.
The near demonstrative is `{!lua}`, whose declension is given below. For distant referents it is `{!ƶua}` and for old information `{!mua}`; they decline in the same way as `{!lua}`.
The adjectival (ADJ) forms of these words are used as determiners before other nouns. Note that unlike most nouns, it is distinct from the genitive: compare `{muƶ kalńł}` 'those cats' and `{mut kalńł}` 'that person's cats'. It also lacks stress, unlike the other forms.
The adjectival (ADJ) forms of these words are used as determiners before other nouns. Note that unlike most nouns, it is distinct from the genitive: compare `{!muƶ kalńł}` 'those cats' and `{!mut kalńł}` 'that person's cats'. It also lacks stress, unlike the other forms.
:::figure
`!SG!` `!PL!`
-------- ----------- -------------
`!NOM!` `{lua}` `{lul}`
`!GEN!` `{lut}` `{lutł}`
`!COM!` `{lukas}` `{luksł}`
`!CAR!` `{lussa}` `{lussal}`
`!INS!` `{lulla}` `{lullal}`
`!ESS!` `{lugu}` `{lugul}`
`!TRA!` `{lusti}` `{lustil}`
`!EXE!` `{luču}` `{lučul}`
`!LOC!` `{lu}` `{lul}`
`!ADJ!` `{luƶ}` `{luƶ}`
`!SG!` `!PL!`
-------- ------------ --------------
`!NOM!` `{!lua}` `{!lul}`
`!GEN!` `{!lut}` `{!lutł}`
`!COM!` `{!lukas}` `{!luksł}`
`!CAR!` `{!lussa}` `{!lussal}`
`!INS!` `{!lulla}` `{!lullal}`
`!ESS!` `{!lugu}` `{!lugul}`
`!TRA!` `{!lusti}` `{!lustil}`
`!EXE!` `{!luču}` `{!lučul}`
`!LOC!` `{!lu}` `{!lul}`
`!ADJ!` `{!luƶ}` `{!luƶ}`
:::

View File

@ -2,6 +2,7 @@
title: Lántas verbs
backname: Lántas
backlink: ../laantas
lang: lántas
...

138
pages/laantas/writing.md Normal file
View File

@ -0,0 +1,138 @@
---
title: Lántas writing
backname: Lántas
backlink: .
lang: lántas
...
Lántas is written with a simple alphasyllabary, where most glyphs consist of
a consonant or cluster with a descender marking the vowel following it. There
are full-sized letters for vowels, used when they start a word or follow
a syllabic consonant. As a quick example, here's the first sentence of
*the North Wind and the Sun*:
:::example
`{!Ruakul naipa bahútlit aimlis Laksit Fuhamkas Guwanḿ asumsas ba sua.
| file = northwind0 ; size = 60 ; stroke = 2 }`
:::
# Vowels
At the start of a word, or after a syllabic consonant, these 'independent'
vowel letters are used.
:::letter-list
`{!a}` `{!á}` `{!i}` `{!í}` `{!u}` `{!ú}`
`{!ai}` `{!au}` `{!ia}` `{!ua}`
`{!ł}` `{!ḿ}` `{!ń}` `{!ŕ}`
:::
In other cases, vowels are attached to the letter for the previous consonant.
:::letter-list
`{!ta}` `{!tá}` `{!ti}` `{!tí}` `{!tu}` `{!tú}`
`{!tai}` `{!tau}` `{!tia}` `{!tua}`
`{!tł}` `{!tḿ}` `{!tń}` `{!tŕ}`
:::
# Consonants
The basic consonant shapes are:
:::letter-list
`{!t\}` `{!k\}` `{!g\}` `{!d\}` `{!ƶ\}` `{!p\}` `{!b\}`
`{!s\}` `{!š\}` `{!l\}` `{!m\}` `{!n\}` `{!č\}` `{!ǧ\}`
`{!w\}` `{!h\}` `{!f\}` `{!j\}`
:::
Clusters are written with a single glyph called a 'conjunct'. These aren't
always just the two letters glued together but they're not usually too
surprising.
<nav>
[`{t}`](#conj-t) ·
[`{ƶ}`](#conj-ƶ) ·
[`{s}`](#conj-s) ·
[`{l}`](#conj-l) ·
[`{m}`](#conj-m) ·
[`{n}`](#conj-n) ·
[`{r}`](#conj-r) ·
[`{}`](#conj-o)
</nav>
::: {.letter-list #conj-t}
`{!tt\}` `{!tk\}` `{!tg\}` `{!td\}` `{!tƶ\}` `{!tp\}` `{!tb\}` `{!ts\}`
`{!tš\}` `{!tl\}` `{!tm\}` `{!tn\}` `{!tr\}` `{!tč\}` `{!tǧ\}` `{!tw\}`
`{!th\}` `{!tf\}` `{!tj\}`
:::
::: {.letter-list #conj-ƶ}
`{!ƶt\}` `{!ƶk\}` `{!ƶg\}` `{!ƶd\}` `{!ƶƶ\}` `{!ƶp\}` `{!ƶb\}` `{!ƶs\}`
`{!ƶš\}` `{!ƶl\}` `{!ƶm\}` `{!ƶn\}` `{!ƶr\}` `{!ƶč\}` `{!ƶǧ\}` `{!ƶw\}`
`{!ƶh\}` `{!ƶf\}` `{!ƶj\}`
:::
::: {.letter-list #conj-s}
`{!st\}` `{!sk\}` `{!sg\}` `{!sd\}` `{!sƶ\}` `{!sp\}` `{!sb\}` `{!ss\}`
`{!sš\}` `{!sl\}` `{!sm\}` `{!sn\}` `{!sr\}` `{!sč\}` `{!sǧ\}` `{!sw\}`
`{!sh\}` `{!sf\}` `{!sj\}` `{!šš\}`
:::
Conjuncts with `{!š\}` are the same as with `{!s\}`, but with the line above. In
the case of `{!šš\}` the lines join up.
::: {.letter-list #conj-l}
`{!lt\}` `{!lk\}` `{!lg\}` `{!ld\}` `{!lƶ\}` `{!lp\}` `{!lb\}` `{!ls\}`
`{!lš\}` `{!ll\}` `{!lm\}` `{!ln\}` `{!lr\}` `{!lč\}` `{!lǧ\}` `{!lw\}`
`{!lh\}` `{!lf\}` `{!lj\}`
:::
::: {.letter-list #conj-m}
`{!mt\}` `{!mk\}` `{!mg\}` `{!md\}` `{!mƶ\}` `{!mp\}` `{!mb\}` `{!ms\}`
`{!mš\}` `{!ml\}` `{!mm\}` `{!mn\}` `{!mr\}` `{!mč\}` `{!mǧ\}` `{!mw\}`
`{!mh\}` `{!mf\}` `{!mj\}`
:::
::: {.letter-list #conj-n}
`{!nt\}` `{!nk\}` `{!ng\}` `{!nd\}` `{!nƶ\}` `{!np\}` `{!nb\}` `{!ns\}`
`{!nš\}` `{!nl\}` `{!nm\}` `{!nn\}` `{!nr\}` `{!nč\}` `{!nǧ\}` `{!nw\}`
`{!nh\}` `{!nf\}` `{!nj\}`
:::
::: {.letter-list #conj-r}
`{!rt\}` `{!rk\}` `{!rg\}` `{!rd\}` `{!rƶ\}` `{!rp\}` `{!rb\}` `{!rs\}`
`{!rš\}` `{!rl\}` `{!rm\}` `{!rn\}` `{!rr\}` `{!rč\}` `{!rǧ\}` `{!rw\}`
`{!rh\}` `{!rf\}` `{!rj\}`
:::
::: {.letter-list #conj-o}
`{!kk\}` `{!ks\}` `{!pp\}` `{!ps\}` `{!pj\}`
`{!bj\}` `{!čs\}` `{!čč\}` `{!hh\}`
`{!hn\}` `{!hm\}` `{!fn\}` `{!fm\}`
:::
# Punctuation
Punctuation in Lántas is very simple. Phrases within a sentence can be separated
by a single circle, and sentences are ended by a double circle:
:::letter-list
`{!ta, ta | file=comma}`
`{!ta. ta | file=fullstop}`
:::
Both have an equal amount of space either side, more for the second one, and if
they are next to a line break they stay with the previous word.
# Numbers
Numbers are written in base 10. Most of the digits are letters, with the
ascenders removed if they had one. Numbers in running text are indicated by
double vertical bars each side, and are grouped in fours.
:::letter-list
`{!0}` `{!1}` `{!2}` `{!3}` `{!4}` `{!5}` `{!6}` `{!7}` `{!8}` `{!9}`
`{!#18 5263 9772#}`
:::