Compare commits
No commits in common. "0cda68e19bfbd2feebaccbaa76bbec7cefce0b78" and "271b69839aaaa5f61b70061d5a2353eb1d86db59" have entirely different histories.
0cda68e19b
...
271b69839a
@ -20,7 +20,6 @@ module Graphics.Fountainhead.Dumper
|
|||||||
, dumpLoca
|
, dumpLoca
|
||||||
, dumpName
|
, dumpName
|
||||||
, dumpMaxp
|
, dumpMaxp
|
||||||
, dumpOs2
|
|
||||||
, dumpPost
|
, dumpPost
|
||||||
, dumpTrueType
|
, dumpTrueType
|
||||||
, dumpOffsetTable
|
, dumpOffsetTable
|
||||||
@ -29,7 +28,7 @@ module Graphics.Fountainhead.Dumper
|
|||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
import qualified Data.ByteString as ByteString
|
import qualified Data.ByteString as ByteString
|
||||||
import qualified Data.ByteString.Char8 as Char8
|
import qualified Data.ByteString.Char8 as Char8
|
||||||
import Data.Int (Int64, Int16)
|
import Data.Int (Int64)
|
||||||
import Data.Word (Word8, Word16, Word32)
|
import Data.Word (Word8, Word16, Word32)
|
||||||
import qualified Data.IntMap as IntMap
|
import qualified Data.IntMap as IntMap
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
@ -67,14 +66,6 @@ import Graphics.Fountainhead.TrueType
|
|||||||
, MaxpTable(..)
|
, MaxpTable(..)
|
||||||
, TrueMaxpTable(..)
|
, TrueMaxpTable(..)
|
||||||
, nameStringOffset
|
, nameStringOffset
|
||||||
, Os2BaseFields(..)
|
|
||||||
, Os2MicrosoftFields(..)
|
|
||||||
, Os2Version1Fields(..)
|
|
||||||
, Os2Version4Fields(..)
|
|
||||||
, Os2Version5Fields(..)
|
|
||||||
, Os2Table(..)
|
|
||||||
, Panose(..)
|
|
||||||
, CVTable(..)
|
|
||||||
)
|
)
|
||||||
import qualified Text.Megaparsec as Megaparsec
|
import qualified Text.Megaparsec as Megaparsec
|
||||||
import Graphics.Fountainhead.Parser
|
import Graphics.Fountainhead.Parser
|
||||||
@ -87,14 +78,13 @@ import Graphics.Fountainhead.Parser
|
|||||||
, locaTableP
|
, locaTableP
|
||||||
, maxpTableP
|
, maxpTableP
|
||||||
, nameTableP
|
, nameTableP
|
||||||
, os2TableP
|
, postTableP
|
||||||
, postTableP, cvTableP
|
|
||||||
)
|
)
|
||||||
import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch)
|
import Graphics.Fountainhead.Type (Fixed32(..), ttfEpoch)
|
||||||
import Data.Foldable (Foldable(..), find)
|
import Data.Foldable (Foldable(..), find)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight)
|
import Data.Time (LocalTime(..), NominalDiffTime, diffLocalTime, midnight)
|
||||||
import Data.Bits (Bits(..), (.>>.))
|
import Data.Bits (Bits(..))
|
||||||
import Data.Bifunctor (Bifunctor(first))
|
import Data.Bifunctor (Bifunctor(first))
|
||||||
import Data.List (intersperse)
|
import Data.List (intersperse)
|
||||||
|
|
||||||
@ -251,149 +241,6 @@ longDateTime localTime = Text.Builder.fromLazyText
|
|||||||
$ (truncate :: NominalDiffTime -> Int)
|
$ (truncate :: NominalDiffTime -> Int)
|
||||||
$ diffLocalTime localTime (LocalTime ttfEpoch midnight)
|
$ diffLocalTime localTime (LocalTime ttfEpoch midnight)
|
||||||
|
|
||||||
dumpCVTable :: CVTable -> Text.Builder.Builder
|
|
||||||
dumpCVTable (CVTable cvTable) = dumpCaption "'cvt ' Table - Control Value Table"
|
|
||||||
<> "Size = " <> Text.Builder.decimal (tableSize * 2)
|
|
||||||
<> " bytes, " <> Text.Builder.decimal tableSize <> " entries\n"
|
|
||||||
<> foldMap (uncurry go) (zip [0..] cvTable)
|
|
||||||
where
|
|
||||||
tableSize = Prelude.length cvTable
|
|
||||||
go :: Int -> Int16 -> Text.Builder.Builder
|
|
||||||
go index' entry = justifyNumber 13 index' <> ". "
|
|
||||||
<> Text.Builder.decimal entry <> newlineBuilder
|
|
||||||
|
|
||||||
dumpOs2 :: Os2Table -> Text.Builder.Builder
|
|
||||||
dumpOs2 = (dumpCaption "'OS/2' Table - OS/2 and Windows Metrics" <>) . go
|
|
||||||
where
|
|
||||||
go = \case
|
|
||||||
Os2Version0 baseFields msFields -> dumpBaseFields baseFields
|
|
||||||
<> maybe "" dumpMicrosoftFields msFields
|
|
||||||
Os2Version1 baseFields msFields extraFields -> dumpBaseFields baseFields
|
|
||||||
<> dumpMicrosoftFields msFields <> dumpVersion1Fields extraFields
|
|
||||||
Os2Version2 baseFields msFields extraFields -> dumpBaseFields baseFields
|
|
||||||
<> dumpMicrosoftFields msFields <> dumpVersion4Fields extraFields
|
|
||||||
Os2Version3 baseFields msFields extraFields -> dumpBaseFields baseFields
|
|
||||||
<> dumpMicrosoftFields msFields <> dumpVersion4Fields extraFields
|
|
||||||
Os2Version4 baseFields msFields extraFields -> dumpBaseFields baseFields
|
|
||||||
<> dumpMicrosoftFields msFields <> dumpVersion4Fields extraFields
|
|
||||||
Os2Version5 baseFields msFields extraFields -> dumpBaseFields baseFields
|
|
||||||
<> dumpMicrosoftFields msFields <> dumpVersion5Fields extraFields
|
|
||||||
dumpVersion1Fields Os2Version1Fields{..}
|
|
||||||
= " CodePage Range 1( Bits 0 - 31 ): " <> paddedHexadecimal ulCodePageRange1 <> newlineBuilder
|
|
||||||
<> " CodePage Range 2( Bits 32- 63 ): " <> paddedHexadecimal ulCodePageRange2 <> newlineBuilder
|
|
||||||
dumpVersion4Fields Os2Version4Fields{..}
|
|
||||||
= dumpVersion1Fields (Os2Version1Fields ulCodePageRange1 ulCodePageRange2)
|
|
||||||
<> " sxHeight: " <> Text.Builder.decimal sxHeight <> newlineBuilder
|
|
||||||
<> " sCapHeight: " <> Text.Builder.decimal sCapHeight <> newlineBuilder
|
|
||||||
<> " usDefaultChar: 0x" <> halfPaddedHexadecimal usDefaultChar <> newlineBuilder
|
|
||||||
<> " usBreakChar: 0x" <> halfPaddedHexadecimal usBreakChar <> newlineBuilder
|
|
||||||
<> " usMaxContext: " <> Text.Builder.decimal usMaxContext <> newlineBuilder
|
|
||||||
dumpVersion5Fields Os2Version5Fields{..}
|
|
||||||
= dumpVersion1Fields (Os2Version1Fields ulCodePageRange1 ulCodePageRange2)
|
|
||||||
<> " sxHeight: " <> Text.Builder.decimal sxHeight <> newlineBuilder
|
|
||||||
<> " sCapHeight: " <> Text.Builder.decimal sCapHeight <> newlineBuilder
|
|
||||||
<> " usDefaultChar: 0x" <> halfPaddedHexadecimal usDefaultChar <> newlineBuilder
|
|
||||||
<> " usBreakChar: 0x" <> halfPaddedHexadecimal usBreakChar <> newlineBuilder
|
|
||||||
<> " usMaxContext: " <> Text.Builder.decimal usMaxContext <> newlineBuilder
|
|
||||||
<> " usLowerOpticalPointSize: "
|
|
||||||
<> Text.Builder.decimal usLowerOpticalPointSize <> newlineBuilder
|
|
||||||
<> " usUpperOpticalPointSize: "
|
|
||||||
<> Text.Builder.decimal usUpperOpticalPointSize <> newlineBuilder
|
|
||||||
dumpMicrosoftFields Os2MicrosoftFields{..}
|
|
||||||
= " sTypoAscender: " <> Text.Builder.decimal sTypoAscender <> newlineBuilder
|
|
||||||
<> " sTypoDescender: " <> Text.Builder.decimal sTypoDescender <> newlineBuilder
|
|
||||||
<> " sTypoLineGap: " <> Text.Builder.decimal sTypoLineGap <> newlineBuilder
|
|
||||||
<> " usWinAscent: " <> Text.Builder.decimal usWinAscent <> newlineBuilder
|
|
||||||
<> " usWinDescent: " <> Text.Builder.decimal usWinDescent <> newlineBuilder
|
|
||||||
dumpBaseFields Os2BaseFields{..}
|
|
||||||
= " 'OS/2' version: " <> Text.Builder.decimal version <> newlineBuilder
|
|
||||||
<> " xAvgCharWidth: " <> Text.Builder.decimal xAvgCharWidth <> newlineBuilder
|
|
||||||
<> " usWeightClass: " <> weightClass usWeightClass <> newlineBuilder
|
|
||||||
<> " usWidthClass: " <> widthClass usWidthClass <> newlineBuilder
|
|
||||||
<> " fsType: " <> Text.Builder.decimal fsType <> newlineBuilder
|
|
||||||
<> " ySubscriptXSize: " <> Text.Builder.decimal ySubscriptXSize <> newlineBuilder
|
|
||||||
<> " ySubscriptYSize: " <> Text.Builder.decimal ySubscriptYSize <> newlineBuilder
|
|
||||||
<> " ySubscriptXOffset: " <> Text.Builder.decimal ySubscriptXOffset <> newlineBuilder
|
|
||||||
<> " ySubscriptYOffset: " <> Text.Builder.decimal ySubscriptYOffset <> newlineBuilder
|
|
||||||
<> " ySuperscriptXSize: " <> Text.Builder.decimal ySuperscriptXSize <> newlineBuilder
|
|
||||||
<> " ySuperscriptYSize: " <> Text.Builder.decimal ySuperscriptYSize <> newlineBuilder
|
|
||||||
<> " ySuperscriptXOffset: " <> Text.Builder.decimal ySuperscriptXOffset <> newlineBuilder
|
|
||||||
<> " ySuperscriptYOffset: " <> Text.Builder.decimal ySuperscriptYOffset <> newlineBuilder
|
|
||||||
<> " yStrikeoutSize: " <> Text.Builder.decimal yStrikeoutSize <> newlineBuilder
|
|
||||||
<> " yStrikeoutPosition: " <> Text.Builder.decimal yStrikeoutPosition <> newlineBuilder
|
|
||||||
<> " sFamilyClass:" <> familyClass sFamilyClass <> newlineBuilder
|
|
||||||
<> " PANOSE:" <> newlineBuilder <> dumpPanose panose
|
|
||||||
<> fold (Vector.imap dumpUnicodeRange ulUnicodeRange)
|
|
||||||
<> " achVendID: '" <> achVendID' achVendID <> "'\n"
|
|
||||||
<> " fsSelection: 0x" <> fsSelection' fsSelection <> newlineBuilder
|
|
||||||
<> " usFirstCharIndex: 0x" <> halfPaddedHexadecimal fsFirstCharIndex <> newlineBuilder
|
|
||||||
<> " usLastCharIndex: 0x" <> halfPaddedHexadecimal fsLastCharIndex <> newlineBuilder
|
|
||||||
fsSelection' value =
|
|
||||||
let description = fold
|
|
||||||
[ if testBit value 0 then "Italic " else ""
|
|
||||||
, if testBit value 5 then "Bold " else ""
|
|
||||||
]
|
|
||||||
in halfPaddedHexadecimal value <> " '" <> description <> "'"
|
|
||||||
achVendID' = Text.Builder.fromText . Text.decodeLatin1 . ByteString.pack . fmap fromIntegral . toList
|
|
||||||
dumpUnicodeRange index value =
|
|
||||||
let bits = index * 32
|
|
||||||
parens = "( Bits " <> Text.Builder.decimal bits <> " - "
|
|
||||||
<> Text.Builder.decimal (bits + 31) <> " ):"
|
|
||||||
in " Unicode Range: " <> Text.Builder.decimal (index + 1)
|
|
||||||
<> Text.Builder.fromLazyText (Text.Lazy.justifyLeft 25 ' ' (Text.Builder.toLazyText parens))
|
|
||||||
<> paddedHexadecimal value
|
|
||||||
<> newlineBuilder
|
|
||||||
dumpPanose Panose{..}
|
|
||||||
= " Family Kind: " <> dumpPanoseField bFamilyType
|
|
||||||
<> " Serif Style: " <> dumpPanoseField bSerifStyle
|
|
||||||
<> " Weight: " <> dumpPanoseField bWeight
|
|
||||||
<> " Proportion: " <> dumpPanoseField bProportion
|
|
||||||
<> " Contrast: " <> dumpPanoseField bContrast
|
|
||||||
<> " Stroke: " <> dumpPanoseField bStrokeVariation
|
|
||||||
<> " Arm Style: " <> dumpPanoseField bArmStyle
|
|
||||||
<> " Lettreform: " <> dumpPanoseField bLetterform
|
|
||||||
<> " Midline: " <> dumpPanoseField bMidline
|
|
||||||
<> " X-height: " <> dumpPanoseField bXHeight
|
|
||||||
dumpPanoseField field' =
|
|
||||||
let numericField = Text.Builder.fromLazyText
|
|
||||||
$ Text.Lazy.justifyLeft 8 ' '
|
|
||||||
$ Text.Builder.toLazyText
|
|
||||||
$ Text.Builder.decimal
|
|
||||||
$ fromEnum field'
|
|
||||||
in numericField
|
|
||||||
<> Text.Builder.singleton '\''
|
|
||||||
<> Text.Builder.fromString (show field')
|
|
||||||
<> Text.Builder.singleton '\''
|
|
||||||
<> newlineBuilder
|
|
||||||
familyClass value =
|
|
||||||
" " <> Text.Builder.decimal (value .>>. 8) <> " subclass = " <> Text.Builder.decimal (value .&. 0x00ff)
|
|
||||||
weightClass classValue
|
|
||||||
| Just wordValue <- fWeight classValue = Text.Builder.decimal classValue <> " '" <> wordValue <> "'"
|
|
||||||
| otherwise = Text.Builder.decimal classValue
|
|
||||||
widthClass classValue
|
|
||||||
| Just wordValue <- fWidth classValue = Text.Builder.decimal classValue <> " '" <> wordValue <> "'"
|
|
||||||
| otherwise = Text.Builder.decimal classValue
|
|
||||||
fWeight 100 = Just "Thin"
|
|
||||||
fWeight 200 = Just "Extra-light"
|
|
||||||
fWeight 300 = Just "Light"
|
|
||||||
fWeight 400 = Just "Normal"
|
|
||||||
fWeight 500 = Just "Medium"
|
|
||||||
fWeight 600 = Just "Semi-bold"
|
|
||||||
fWeight 700 = Just "Bold"
|
|
||||||
fWeight 800 = Just "Extra-bold"
|
|
||||||
fWeight 900 = Just "Black"
|
|
||||||
fWeight _ = Nothing
|
|
||||||
fWidth 1 = Just "Ultra-condensed"
|
|
||||||
fWidth 2 = Just "Extra-condensed"
|
|
||||||
fWidth 3 = Just "Condensed"
|
|
||||||
fWidth 4 = Just "Semi-condensed"
|
|
||||||
fWidth 5 = Just "Medium"
|
|
||||||
fWidth 6 = Just "Semi-expanded"
|
|
||||||
fWidth 7 = Just "Expanded"
|
|
||||||
fWidth 8 = Just "Extra-expanded"
|
|
||||||
fWidth 9 = Just "Ultra-expanded"
|
|
||||||
fWidth _ = Nothing
|
|
||||||
|
|
||||||
dumpPost :: PostTable -> Text.Builder.Builder
|
dumpPost :: PostTable -> Text.Builder.Builder
|
||||||
dumpPost PostTable{ postHeader = PostHeader{..}, postSubtable }
|
dumpPost PostTable{ postHeader = PostHeader{..}, postSubtable }
|
||||||
= dumpCaption "'post' Table - PostScript" <> newlineBuilder
|
= dumpCaption "'post' Table - PostScript" <> newlineBuilder
|
||||||
@ -653,8 +500,6 @@ dumpTables processedState directory@FontDirectory{..}
|
|||||||
"maxp" -> Just $ dumpMaxp <$> parseTable tableEntry maxpTableP processedState
|
"maxp" -> Just $ dumpMaxp <$> parseTable tableEntry maxpTableP processedState
|
||||||
"name" -> Just $ dumpName <$> parseTable tableEntry nameTableP processedState
|
"name" -> Just $ dumpName <$> parseTable tableEntry nameTableP processedState
|
||||||
"post" -> Just $ dumpPost <$> parseTable tableEntry postTableP processedState
|
"post" -> Just $ dumpPost <$> parseTable tableEntry postTableP processedState
|
||||||
"OS/2" -> Just $ dumpOs2 <$> parseTable tableEntry os2TableP processedState
|
|
||||||
"cvt " -> Just $ dumpCVTable <$> parseTable tableEntry cvTableP processedState
|
|
||||||
_ -> Nothing
|
_ -> Nothing
|
||||||
|
|
||||||
dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder
|
dumpTrueType :: ByteString -> FilePath -> Either DumpError Text.Builder.Builder
|
||||||
|
@ -720,7 +720,7 @@ cmapFormat14TableP = do
|
|||||||
currentOffset <- Megaparsec.getOffset
|
currentOffset <- Megaparsec.getOffset
|
||||||
let emptyBytes = tableOffset + fromIntegral relativeOffset - currentOffset
|
let emptyBytes = tableOffset + fromIntegral relativeOffset - currentOffset
|
||||||
relativeOffset' = fromIntegral relativeOffset
|
relativeOffset' = fromIntegral relativeOffset
|
||||||
void $ Megaparsec.takeP Nothing emptyBytes
|
Megaparsec.takeP Nothing emptyBytes
|
||||||
entryCount <- fromIntegral <$> Megaparsec.Binary.word32be
|
entryCount <- fromIntegral <$> Megaparsec.Binary.word32be
|
||||||
valueRanges <- vectorNP entryCount unicodeValueRangeP
|
valueRanges <- vectorNP entryCount unicodeValueRangeP
|
||||||
pure $ IntMap.insert relativeOffset' (DefaultUVSOffset varSelector' valueRanges :| []) accumulator
|
pure $ IntMap.insert relativeOffset' (DefaultUVSOffset varSelector' valueRanges :| []) accumulator
|
||||||
@ -734,7 +734,7 @@ cmapFormat14TableP = do
|
|||||||
| otherwise = do
|
| otherwise = do
|
||||||
currentOffset <- Megaparsec.getOffset
|
currentOffset <- Megaparsec.getOffset
|
||||||
let emptyBytes = tableOffset + fromIntegral relativeOffset - currentOffset
|
let emptyBytes = tableOffset + fromIntegral relativeOffset - currentOffset
|
||||||
void $ Megaparsec.takeP Nothing emptyBytes
|
Megaparsec.takeP Nothing emptyBytes
|
||||||
entryCount <- fromIntegral <$> Megaparsec.Binary.word32be
|
entryCount <- fromIntegral <$> Megaparsec.Binary.word32be
|
||||||
flip (IntMap.insert $ fromIntegral relativeOffset) accumulator
|
flip (IntMap.insert $ fromIntegral relativeOffset) accumulator
|
||||||
. pure
|
. pure
|
||||||
@ -1135,15 +1135,15 @@ bContrastP
|
|||||||
|
|
||||||
bStrokeVariationP :: Parser BStrokeVariation
|
bStrokeVariationP :: Parser BStrokeVariation
|
||||||
bStrokeVariationP
|
bStrokeVariationP
|
||||||
= (Megaparsec.single 0 $> AnyStrokeVariation)
|
= (Megaparsec.single 0 $> AnyStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 1 $> NoFitStrokeVariation)
|
<|> (Megaparsec.single 1 $> NoFitStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 2 $> GradualDiagonalStrokeVariation)
|
<|> (Megaparsec.single 2 $> GradualDiagonalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 3 $> GradualTransitionalStrokeVariation)
|
<|> (Megaparsec.single 3 $> GradualTransitionalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 4 $> GradualVerticalStrokeVariation)
|
<|> (Megaparsec.single 4 $> GradualVerticalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 5 $> GradualHorizontalStrokeVariation)
|
<|> (Megaparsec.single 5 $> GradualHorizontalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 6 $> RapidVerticalStrokeVariation)
|
<|> (Megaparsec.single 6 $> RapidVerticalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 7 $> RapidHorizontalStrokeVariation)
|
<|> (Megaparsec.single 7 $> RapidHorizontalStrokeVariatoon)
|
||||||
<|> (Megaparsec.single 8 $> InstantVerticalStrokeVariation)
|
<|> (Megaparsec.single 8 $> InstantVerticalStrokeVariatoon)
|
||||||
<?> "bStrokeVariation"
|
<?> "bStrokeVariation"
|
||||||
|
|
||||||
bArmStyleP :: Parser BArmStyle
|
bArmStyleP :: Parser BArmStyle
|
||||||
|
@ -627,32 +627,7 @@ data BFamilyType
|
|||||||
| ScriptFamilyType
|
| ScriptFamilyType
|
||||||
| DecorativeFamilyType
|
| DecorativeFamilyType
|
||||||
| PictorialFamilyType
|
| PictorialFamilyType
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BFamilyType
|
|
||||||
where
|
|
||||||
show AnyFamilyType = "Any"
|
|
||||||
show NoFitFamilyType = "No Fit"
|
|
||||||
show TextAndDisplayFamilyType = "Text and Display"
|
|
||||||
show ScriptFamilyType = "Script"
|
|
||||||
show DecorativeFamilyType = "Decorative"
|
|
||||||
show PictorialFamilyType = "Pictorial"
|
|
||||||
|
|
||||||
instance Enum BFamilyType
|
|
||||||
where
|
|
||||||
toEnum 0 = AnyFamilyType
|
|
||||||
toEnum 1 = NoFitFamilyType
|
|
||||||
toEnum 2 = TextAndDisplayFamilyType
|
|
||||||
toEnum 3 = ScriptFamilyType
|
|
||||||
toEnum 4 = DecorativeFamilyType
|
|
||||||
toEnum 5 = PictorialFamilyType
|
|
||||||
toEnum _ = error "Unknown family type"
|
|
||||||
fromEnum AnyFamilyType = 0
|
|
||||||
fromEnum NoFitFamilyType = 1
|
|
||||||
fromEnum TextAndDisplayFamilyType = 2
|
|
||||||
fromEnum ScriptFamilyType = 3
|
|
||||||
fromEnum DecorativeFamilyType = 4
|
|
||||||
fromEnum PictorialFamilyType = 5
|
|
||||||
|
|
||||||
data BSerifStyle
|
data BSerifStyle
|
||||||
= AnySerifStyle
|
= AnySerifStyle
|
||||||
@ -671,62 +646,7 @@ data BSerifStyle
|
|||||||
| PerpSansSerifStyle
|
| PerpSansSerifStyle
|
||||||
| FlaredSerifStyle
|
| FlaredSerifStyle
|
||||||
| RoundedSerifStyle
|
| RoundedSerifStyle
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BSerifStyle
|
|
||||||
where
|
|
||||||
show AnySerifStyle = "Any"
|
|
||||||
show NoFitSerifStyle = "No Fit"
|
|
||||||
show CoveSerifStyle = "Cove"
|
|
||||||
show ObtuseCoveSerifStyle = "Obtuse Cove"
|
|
||||||
show SquareCoveSerifStyle = "Square Cove"
|
|
||||||
show ObtuseSquareCoveSerifStyle = "Obtuse Square Cove"
|
|
||||||
show SquareSerifStyle = "Square"
|
|
||||||
show ThinSerifStyle = "Thin"
|
|
||||||
show BoneSerifStyle = "Bone"
|
|
||||||
show ExaggeratedSerifStyle = "Exaggerated"
|
|
||||||
show TriangleSerifStyle = "Triangle"
|
|
||||||
show NormalSansSerifStyle = "Normal Sans"
|
|
||||||
show ObtuseSansSerifStyle = "Obtuse Sans"
|
|
||||||
show PerpSansSerifStyle = "Perp Sans"
|
|
||||||
show FlaredSerifStyle = "Flared"
|
|
||||||
show RoundedSerifStyle = "Rounded"
|
|
||||||
|
|
||||||
instance Enum BSerifStyle
|
|
||||||
where
|
|
||||||
toEnum 0 = AnySerifStyle
|
|
||||||
toEnum 1 = NoFitSerifStyle
|
|
||||||
toEnum 2 = CoveSerifStyle
|
|
||||||
toEnum 3 = ObtuseCoveSerifStyle
|
|
||||||
toEnum 4 = SquareCoveSerifStyle
|
|
||||||
toEnum 5 = ObtuseSquareCoveSerifStyle
|
|
||||||
toEnum 6 = SquareSerifStyle
|
|
||||||
toEnum 7 = ThinSerifStyle
|
|
||||||
toEnum 8 = BoneSerifStyle
|
|
||||||
toEnum 9 = ExaggeratedSerifStyle
|
|
||||||
toEnum 10 = TriangleSerifStyle
|
|
||||||
toEnum 11 = NormalSansSerifStyle
|
|
||||||
toEnum 12 = ObtuseSansSerifStyle
|
|
||||||
toEnum 13 = PerpSansSerifStyle
|
|
||||||
toEnum 14 = FlaredSerifStyle
|
|
||||||
toEnum 15 = RoundedSerifStyle
|
|
||||||
toEnum _ = error "Unknown serif type"
|
|
||||||
fromEnum AnySerifStyle = 0
|
|
||||||
fromEnum NoFitSerifStyle = 1
|
|
||||||
fromEnum CoveSerifStyle = 2
|
|
||||||
fromEnum ObtuseCoveSerifStyle = 3
|
|
||||||
fromEnum SquareCoveSerifStyle = 4
|
|
||||||
fromEnum ObtuseSquareCoveSerifStyle = 5
|
|
||||||
fromEnum SquareSerifStyle = 6
|
|
||||||
fromEnum ThinSerifStyle = 7
|
|
||||||
fromEnum BoneSerifStyle = 8
|
|
||||||
fromEnum ExaggeratedSerifStyle = 9
|
|
||||||
fromEnum TriangleSerifStyle = 10
|
|
||||||
fromEnum NormalSansSerifStyle = 11
|
|
||||||
fromEnum ObtuseSansSerifStyle = 12
|
|
||||||
fromEnum PerpSansSerifStyle = 13
|
|
||||||
fromEnum FlaredSerifStyle = 14
|
|
||||||
fromEnum RoundedSerifStyle = 15
|
|
||||||
|
|
||||||
data BWeight
|
data BWeight
|
||||||
= AnyWeight
|
= AnyWeight
|
||||||
@ -741,50 +661,7 @@ data BWeight
|
|||||||
| HeavyWeight
|
| HeavyWeight
|
||||||
| BlackWeight
|
| BlackWeight
|
||||||
| NordWeight
|
| NordWeight
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BWeight
|
|
||||||
where
|
|
||||||
show AnyWeight = "Any"
|
|
||||||
show NoFitWeight = "No Fit"
|
|
||||||
show VeryLightWeight = "Very Light"
|
|
||||||
show LightWeight = "Light"
|
|
||||||
show ThinWeight = "Thin"
|
|
||||||
show BookWeight = "Book"
|
|
||||||
show MediumWeight = "Medium"
|
|
||||||
show DemiWeight = "Demi"
|
|
||||||
show BoldWeight = "Bold"
|
|
||||||
show HeavyWeight = "Heavy"
|
|
||||||
show BlackWeight = "Black"
|
|
||||||
show NordWeight = "Nord"
|
|
||||||
|
|
||||||
instance Enum BWeight
|
|
||||||
where
|
|
||||||
fromEnum AnyWeight = 0
|
|
||||||
fromEnum NoFitWeight = 1
|
|
||||||
fromEnum VeryLightWeight = 2
|
|
||||||
fromEnum LightWeight = 3
|
|
||||||
fromEnum ThinWeight = 4
|
|
||||||
fromEnum BookWeight = 5
|
|
||||||
fromEnum MediumWeight = 6
|
|
||||||
fromEnum DemiWeight = 7
|
|
||||||
fromEnum BoldWeight = 8
|
|
||||||
fromEnum HeavyWeight = 9
|
|
||||||
fromEnum BlackWeight = 10
|
|
||||||
fromEnum NordWeight = 11
|
|
||||||
toEnum 0 = AnyWeight
|
|
||||||
toEnum 1 = NoFitWeight
|
|
||||||
toEnum 2 = VeryLightWeight
|
|
||||||
toEnum 3 = LightWeight
|
|
||||||
toEnum 4 = ThinWeight
|
|
||||||
toEnum 5 = BookWeight
|
|
||||||
toEnum 6 = MediumWeight
|
|
||||||
toEnum 7 = DemiWeight
|
|
||||||
toEnum 8 = BoldWeight
|
|
||||||
toEnum 9 = HeavyWeight
|
|
||||||
toEnum 10 = BlackWeight
|
|
||||||
toEnum 11 = NordWeight
|
|
||||||
toEnum _ = error "Unknown weight"
|
|
||||||
|
|
||||||
data BProportion
|
data BProportion
|
||||||
= AnyProportion
|
= AnyProportion
|
||||||
@ -797,44 +674,7 @@ data BProportion
|
|||||||
| VeryExpandedProportion
|
| VeryExpandedProportion
|
||||||
| VeryCondensedProportion
|
| VeryCondensedProportion
|
||||||
| MonospacedProportion
|
| MonospacedProportion
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BProportion
|
|
||||||
where
|
|
||||||
show AnyProportion = "Any"
|
|
||||||
show NoFitProportion = "No Fit"
|
|
||||||
show OldStyleProportion = "Old Style"
|
|
||||||
show ModernProportion = "Modern"
|
|
||||||
show EvenWidthProportion = "Even Width"
|
|
||||||
show ExpandedProportion = "Expanded"
|
|
||||||
show CondensedProportion = "Condensed"
|
|
||||||
show VeryExpandedProportion = "Very Expanded"
|
|
||||||
show VeryCondensedProportion = "Very Condensed"
|
|
||||||
show MonospacedProportion = "Monospaced"
|
|
||||||
|
|
||||||
instance Enum BProportion
|
|
||||||
where
|
|
||||||
fromEnum AnyProportion = 0
|
|
||||||
fromEnum NoFitProportion = 1
|
|
||||||
fromEnum OldStyleProportion = 2
|
|
||||||
fromEnum ModernProportion = 3
|
|
||||||
fromEnum EvenWidthProportion = 4
|
|
||||||
fromEnum ExpandedProportion = 5
|
|
||||||
fromEnum CondensedProportion = 6
|
|
||||||
fromEnum VeryExpandedProportion = 7
|
|
||||||
fromEnum VeryCondensedProportion = 8
|
|
||||||
fromEnum MonospacedProportion = 9
|
|
||||||
toEnum 0 = AnyProportion
|
|
||||||
toEnum 1 = NoFitProportion
|
|
||||||
toEnum 2 = OldStyleProportion
|
|
||||||
toEnum 3 = ModernProportion
|
|
||||||
toEnum 4 = EvenWidthProportion
|
|
||||||
toEnum 5 = ExpandedProportion
|
|
||||||
toEnum 6 = CondensedProportion
|
|
||||||
toEnum 7 = VeryExpandedProportion
|
|
||||||
toEnum 8 = VeryCondensedProportion
|
|
||||||
toEnum 9 = MonospacedProportion
|
|
||||||
toEnum _ = error "Unknown proportion"
|
|
||||||
|
|
||||||
data BContrast
|
data BContrast
|
||||||
= AnyContrast
|
= AnyContrast
|
||||||
@ -847,90 +687,19 @@ data BContrast
|
|||||||
| MediumHighContrast
|
| MediumHighContrast
|
||||||
| HighContrast
|
| HighContrast
|
||||||
| VeryHighContrast
|
| VeryHighContrast
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BContrast
|
|
||||||
where
|
|
||||||
show AnyContrast = "Any"
|
|
||||||
show NoFitContrast = "No Fit"
|
|
||||||
show NoneContrast = "None"
|
|
||||||
show VeryLowContrast = "Very Low"
|
|
||||||
show LowContrast = "Low"
|
|
||||||
show MediumLowContrast = "Medium Low"
|
|
||||||
show MediumContrast = "Medium"
|
|
||||||
show MediumHighContrast = "Medium High"
|
|
||||||
show HighContrast = "High"
|
|
||||||
show VeryHighContrast = "Very High"
|
|
||||||
|
|
||||||
instance Enum BContrast
|
|
||||||
where
|
|
||||||
fromEnum AnyContrast = 0
|
|
||||||
fromEnum NoFitContrast = 1
|
|
||||||
fromEnum NoneContrast = 2
|
|
||||||
fromEnum VeryLowContrast = 3
|
|
||||||
fromEnum LowContrast = 4
|
|
||||||
fromEnum MediumLowContrast = 5
|
|
||||||
fromEnum MediumContrast = 6
|
|
||||||
fromEnum MediumHighContrast = 7
|
|
||||||
fromEnum HighContrast = 8
|
|
||||||
fromEnum VeryHighContrast = 9
|
|
||||||
toEnum 0 = AnyContrast
|
|
||||||
toEnum 1 = NoFitContrast
|
|
||||||
toEnum 2 = NoneContrast
|
|
||||||
toEnum 3 = VeryLowContrast
|
|
||||||
toEnum 4 = LowContrast
|
|
||||||
toEnum 5 = MediumLowContrast
|
|
||||||
toEnum 6 = MediumContrast
|
|
||||||
toEnum 7 = MediumHighContrast
|
|
||||||
toEnum 8 = HighContrast
|
|
||||||
toEnum 9 = VeryHighContrast
|
|
||||||
toEnum _ = error "Unknown contrast"
|
|
||||||
|
|
||||||
data BStrokeVariation
|
data BStrokeVariation
|
||||||
= AnyStrokeVariation
|
= AnyStrokeVariatoon
|
||||||
| NoFitStrokeVariation
|
| NoFitStrokeVariatoon
|
||||||
| GradualDiagonalStrokeVariation
|
| GradualDiagonalStrokeVariatoon
|
||||||
| GradualTransitionalStrokeVariation
|
| GradualTransitionalStrokeVariatoon
|
||||||
| GradualVerticalStrokeVariation
|
| GradualVerticalStrokeVariatoon
|
||||||
| GradualHorizontalStrokeVariation
|
| GradualHorizontalStrokeVariatoon
|
||||||
| RapidVerticalStrokeVariation
|
| RapidVerticalStrokeVariatoon
|
||||||
| RapidHorizontalStrokeVariation
|
| RapidHorizontalStrokeVariatoon
|
||||||
| InstantVerticalStrokeVariation
|
| InstantVerticalStrokeVariatoon
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BStrokeVariation
|
|
||||||
where
|
|
||||||
show AnyStrokeVariation = "Any"
|
|
||||||
show NoFitStrokeVariation = "No Fit"
|
|
||||||
show GradualDiagonalStrokeVariation = "Gradual/Diagonal"
|
|
||||||
show GradualTransitionalStrokeVariation = "Gradual/Transitional"
|
|
||||||
show GradualVerticalStrokeVariation = "Gradual/Vertical"
|
|
||||||
show GradualHorizontalStrokeVariation = "Gradual/Horizontal"
|
|
||||||
show RapidVerticalStrokeVariation = "Rapid/Vertical"
|
|
||||||
show RapidHorizontalStrokeVariation = "Rapid/Horizontal"
|
|
||||||
show InstantVerticalStrokeVariation = "Instant/Vertical"
|
|
||||||
|
|
||||||
instance Enum BStrokeVariation
|
|
||||||
where
|
|
||||||
fromEnum AnyStrokeVariation = 0
|
|
||||||
fromEnum NoFitStrokeVariation = 1
|
|
||||||
fromEnum GradualDiagonalStrokeVariation = 2
|
|
||||||
fromEnum GradualTransitionalStrokeVariation = 3
|
|
||||||
fromEnum GradualVerticalStrokeVariation = 4
|
|
||||||
fromEnum GradualHorizontalStrokeVariation = 5
|
|
||||||
fromEnum RapidVerticalStrokeVariation = 6
|
|
||||||
fromEnum RapidHorizontalStrokeVariation = 7
|
|
||||||
fromEnum InstantVerticalStrokeVariation = 8
|
|
||||||
toEnum 0 = AnyStrokeVariation
|
|
||||||
toEnum 1 = NoFitStrokeVariation
|
|
||||||
toEnum 2 = GradualDiagonalStrokeVariation
|
|
||||||
toEnum 3 = GradualTransitionalStrokeVariation
|
|
||||||
toEnum 4 = GradualVerticalStrokeVariation
|
|
||||||
toEnum 5 = GradualHorizontalStrokeVariation
|
|
||||||
toEnum 6 = RapidVerticalStrokeVariation
|
|
||||||
toEnum 7 = RapidHorizontalStrokeVariation
|
|
||||||
toEnum 8 = InstantVerticalStrokeVariation
|
|
||||||
toEnum _ = error "Unknown stroke variation"
|
|
||||||
|
|
||||||
data BArmStyle
|
data BArmStyle
|
||||||
= AnyArmStyle
|
= AnyArmStyle
|
||||||
@ -945,50 +714,7 @@ data BArmStyle
|
|||||||
| NonStraightArmsVerticalArmStyle
|
| NonStraightArmsVerticalArmStyle
|
||||||
| NonStraightArmsSingleSerifArmStyle
|
| NonStraightArmsSingleSerifArmStyle
|
||||||
| NonStraightArmsDoubleSerifArmStyle
|
| NonStraightArmsDoubleSerifArmStyle
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BArmStyle
|
|
||||||
where
|
|
||||||
show AnyArmStyle = "Any"
|
|
||||||
show NoFitArmStyle = "No Fit"
|
|
||||||
show StraightArmsHorizontalArmStyle = "Straight Arms/Horizontal"
|
|
||||||
show StraightArmsWedgeArmStyle = "Straight Arms/Wedge"
|
|
||||||
show StraightArmsVerticalArmStyle = "Straight Arms/Vertical"
|
|
||||||
show StraightArmsSingleSerifArmStyle = "Straight Arms/Single Serif"
|
|
||||||
show StraightArmsDoubleSerifArmStyle = "Straight Arms/Double Serif"
|
|
||||||
show NonStraightArmsHorizontalArmStyle = "Non-Straight Arms/Horizontal"
|
|
||||||
show NonStraightArmsWedgeArmStyle = "Non-Straight Arms/Wedge"
|
|
||||||
show NonStraightArmsVerticalArmStyle = "Non-Straight Arms/Vertical"
|
|
||||||
show NonStraightArmsSingleSerifArmStyle = "Non-Straight Arms/Single Serif"
|
|
||||||
show NonStraightArmsDoubleSerifArmStyle = "Non-Straight Arms/Double Serif"
|
|
||||||
|
|
||||||
instance Enum BArmStyle
|
|
||||||
where
|
|
||||||
fromEnum AnyArmStyle = 0
|
|
||||||
fromEnum NoFitArmStyle = 1
|
|
||||||
fromEnum StraightArmsHorizontalArmStyle = 2
|
|
||||||
fromEnum StraightArmsWedgeArmStyle = 3
|
|
||||||
fromEnum StraightArmsVerticalArmStyle = 4
|
|
||||||
fromEnum StraightArmsSingleSerifArmStyle = 5
|
|
||||||
fromEnum StraightArmsDoubleSerifArmStyle = 6
|
|
||||||
fromEnum NonStraightArmsHorizontalArmStyle = 7
|
|
||||||
fromEnum NonStraightArmsWedgeArmStyle = 8
|
|
||||||
fromEnum NonStraightArmsVerticalArmStyle = 9
|
|
||||||
fromEnum NonStraightArmsSingleSerifArmStyle = 10
|
|
||||||
fromEnum NonStraightArmsDoubleSerifArmStyle = 11
|
|
||||||
toEnum 0 = AnyArmStyle
|
|
||||||
toEnum 1 = NoFitArmStyle
|
|
||||||
toEnum 2 = StraightArmsHorizontalArmStyle
|
|
||||||
toEnum 3 = StraightArmsWedgeArmStyle
|
|
||||||
toEnum 4 = StraightArmsVerticalArmStyle
|
|
||||||
toEnum 5 = StraightArmsSingleSerifArmStyle
|
|
||||||
toEnum 6 = StraightArmsDoubleSerifArmStyle
|
|
||||||
toEnum 7 = NonStraightArmsHorizontalArmStyle
|
|
||||||
toEnum 8 = NonStraightArmsWedgeArmStyle
|
|
||||||
toEnum 9 = NonStraightArmsVerticalArmStyle
|
|
||||||
toEnum 10 = NonStraightArmsSingleSerifArmStyle
|
|
||||||
toEnum 11 = NonStraightArmsDoubleSerifArmStyle
|
|
||||||
toEnum _ = error "Unknown arm style"
|
|
||||||
|
|
||||||
data BLetterform
|
data BLetterform
|
||||||
= AnyLetterform
|
= AnyLetterform
|
||||||
@ -1007,62 +733,7 @@ data BLetterform
|
|||||||
| ObliqueRoundedLetterform
|
| ObliqueRoundedLetterform
|
||||||
| ObliqueOffCenterLetterform
|
| ObliqueOffCenterLetterform
|
||||||
| ObliqueSquareLetterform
|
| ObliqueSquareLetterform
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BLetterform
|
|
||||||
where
|
|
||||||
show AnyLetterform = "Any"
|
|
||||||
show NoFitLetterform = "No Fit"
|
|
||||||
show NormalContactLetterform = "Normal/Contact"
|
|
||||||
show NormalWeightedLetterform = "Normal/Weighted"
|
|
||||||
show NormalBoxedLetterform = "Normal/Boxed"
|
|
||||||
show NormalFlattenedLetterform = "Normal/Flattened"
|
|
||||||
show NormalRoundedLetterform = "Normal/Rounded"
|
|
||||||
show NormalOffCenterLetterform = "Normal/Off Center"
|
|
||||||
show NormalSquareLetterform = "Normal/Square"
|
|
||||||
show ObliqueContactLetterform = "Oblique/Contact"
|
|
||||||
show ObliqueWeightedLetterform = "Oblique/Weighted"
|
|
||||||
show ObliqueBoxedLetterform = "Oblique/Boxed"
|
|
||||||
show ObliqueFlattenedLetterform = "Oblique/Flattened"
|
|
||||||
show ObliqueRoundedLetterform = "Oblique/Rounded"
|
|
||||||
show ObliqueOffCenterLetterform = "Oblique/Off Center"
|
|
||||||
show ObliqueSquareLetterform = "Oblique/Square"
|
|
||||||
|
|
||||||
instance Enum BLetterform
|
|
||||||
where
|
|
||||||
fromEnum AnyLetterform = 0
|
|
||||||
fromEnum NoFitLetterform = 1
|
|
||||||
fromEnum NormalContactLetterform = 2
|
|
||||||
fromEnum NormalWeightedLetterform = 3
|
|
||||||
fromEnum NormalBoxedLetterform = 4
|
|
||||||
fromEnum NormalFlattenedLetterform = 5
|
|
||||||
fromEnum NormalRoundedLetterform = 6
|
|
||||||
fromEnum NormalOffCenterLetterform = 7
|
|
||||||
fromEnum NormalSquareLetterform = 8
|
|
||||||
fromEnum ObliqueContactLetterform = 9
|
|
||||||
fromEnum ObliqueWeightedLetterform = 10
|
|
||||||
fromEnum ObliqueBoxedLetterform = 11
|
|
||||||
fromEnum ObliqueFlattenedLetterform = 12
|
|
||||||
fromEnum ObliqueRoundedLetterform = 13
|
|
||||||
fromEnum ObliqueOffCenterLetterform = 14
|
|
||||||
fromEnum ObliqueSquareLetterform = 15
|
|
||||||
toEnum 0 = AnyLetterform
|
|
||||||
toEnum 1 = NoFitLetterform
|
|
||||||
toEnum 2 = NormalContactLetterform
|
|
||||||
toEnum 3 = NormalWeightedLetterform
|
|
||||||
toEnum 4 = NormalBoxedLetterform
|
|
||||||
toEnum 5 = NormalFlattenedLetterform
|
|
||||||
toEnum 6 = NormalRoundedLetterform
|
|
||||||
toEnum 7 = NormalOffCenterLetterform
|
|
||||||
toEnum 8 = NormalSquareLetterform
|
|
||||||
toEnum 9 = ObliqueContactLetterform
|
|
||||||
toEnum 10 = ObliqueWeightedLetterform
|
|
||||||
toEnum 11 = ObliqueBoxedLetterform
|
|
||||||
toEnum 12 = ObliqueFlattenedLetterform
|
|
||||||
toEnum 13 = ObliqueRoundedLetterform
|
|
||||||
toEnum 14 = ObliqueOffCenterLetterform
|
|
||||||
toEnum 15 = ObliqueSquareLetterform
|
|
||||||
toEnum _ = error "Unknown letterform"
|
|
||||||
|
|
||||||
data BMidline
|
data BMidline
|
||||||
= AnyMidline
|
= AnyMidline
|
||||||
@ -1079,56 +750,7 @@ data BMidline
|
|||||||
| LowTrimmedMidline
|
| LowTrimmedMidline
|
||||||
| LowPointedMidline
|
| LowPointedMidline
|
||||||
| LowSerifedMidline
|
| LowSerifedMidline
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BMidline
|
|
||||||
where
|
|
||||||
show AnyMidline = "Any"
|
|
||||||
show NoFitMidline = "No Fit"
|
|
||||||
show StandardTrimmedMidline = "Standard/Trimmed"
|
|
||||||
show StandardPointedMidline = "Standard/Pointed"
|
|
||||||
show StandardSerifedMidline = "Standard/Serifed"
|
|
||||||
show HighTrimmedMidline = "High/Trimmed"
|
|
||||||
show HighPointedMidline = "High/Pointed"
|
|
||||||
show HighSerifedMidline = "High/Serifed"
|
|
||||||
show ConstantTrimmedMidline = "Constant/Trimmed"
|
|
||||||
show ConstantPointedMidline = "Constant/Pointed"
|
|
||||||
show ConstantSerifedMidline = "Constant/Serifed"
|
|
||||||
show LowTrimmedMidline = "Low/Trimmed"
|
|
||||||
show LowPointedMidline = "Low/Pointed"
|
|
||||||
show LowSerifedMidline = "Low/Serifed"
|
|
||||||
|
|
||||||
instance Enum BMidline
|
|
||||||
where
|
|
||||||
fromEnum AnyMidline = 0
|
|
||||||
fromEnum NoFitMidline = 1
|
|
||||||
fromEnum StandardTrimmedMidline = 2
|
|
||||||
fromEnum StandardPointedMidline = 3
|
|
||||||
fromEnum StandardSerifedMidline = 4
|
|
||||||
fromEnum HighTrimmedMidline = 5
|
|
||||||
fromEnum HighPointedMidline = 6
|
|
||||||
fromEnum HighSerifedMidline = 7
|
|
||||||
fromEnum ConstantTrimmedMidline = 8
|
|
||||||
fromEnum ConstantPointedMidline = 9
|
|
||||||
fromEnum ConstantSerifedMidline = 10
|
|
||||||
fromEnum LowTrimmedMidline = 11
|
|
||||||
fromEnum LowPointedMidline = 12
|
|
||||||
fromEnum LowSerifedMidline = 13
|
|
||||||
toEnum 0 = AnyMidline
|
|
||||||
toEnum 1 = NoFitMidline
|
|
||||||
toEnum 2 = StandardTrimmedMidline
|
|
||||||
toEnum 3 = StandardPointedMidline
|
|
||||||
toEnum 4 = StandardSerifedMidline
|
|
||||||
toEnum 5 = HighTrimmedMidline
|
|
||||||
toEnum 6 = HighPointedMidline
|
|
||||||
toEnum 7 = HighSerifedMidline
|
|
||||||
toEnum 8 = ConstantTrimmedMidline
|
|
||||||
toEnum 9 = ConstantPointedMidline
|
|
||||||
toEnum 10 = ConstantSerifedMidline
|
|
||||||
toEnum 11 = LowTrimmedMidline
|
|
||||||
toEnum 12 = LowPointedMidline
|
|
||||||
toEnum 13 = LowSerifedMidline
|
|
||||||
toEnum _ = error "Unknown midline"
|
|
||||||
|
|
||||||
data BXHeight
|
data BXHeight
|
||||||
= AnyXHeight
|
= AnyXHeight
|
||||||
@ -1139,38 +761,7 @@ data BXHeight
|
|||||||
| DuckingSmallXHeight
|
| DuckingSmallXHeight
|
||||||
| DuckingStandardXHeight
|
| DuckingStandardXHeight
|
||||||
| DuckingLargeXHeight
|
| DuckingLargeXHeight
|
||||||
deriving Eq
|
deriving (Eq, Show)
|
||||||
|
|
||||||
instance Show BXHeight
|
|
||||||
where
|
|
||||||
show AnyXHeight = "Any"
|
|
||||||
show NoFitXHeight = "No Fit"
|
|
||||||
show ConstantSmallXHeight = "Constant/Small"
|
|
||||||
show ConstantStandardXHeight = "Constant/Standard"
|
|
||||||
show ConstantLargeXHeight = "Constant/Large"
|
|
||||||
show DuckingSmallXHeight = "Ducking/Small"
|
|
||||||
show DuckingStandardXHeight = "Ducking/Standard"
|
|
||||||
show DuckingLargeXHeight = "Ducking/Large"
|
|
||||||
|
|
||||||
instance Enum BXHeight
|
|
||||||
where
|
|
||||||
fromEnum AnyXHeight = 0
|
|
||||||
fromEnum NoFitXHeight = 1
|
|
||||||
fromEnum ConstantSmallXHeight = 2
|
|
||||||
fromEnum ConstantStandardXHeight = 3
|
|
||||||
fromEnum ConstantLargeXHeight = 4
|
|
||||||
fromEnum DuckingSmallXHeight = 5
|
|
||||||
fromEnum DuckingStandardXHeight = 6
|
|
||||||
fromEnum DuckingLargeXHeight = 7
|
|
||||||
toEnum 0 = AnyXHeight
|
|
||||||
toEnum 1 = NoFitXHeight
|
|
||||||
toEnum 2 = ConstantSmallXHeight
|
|
||||||
toEnum 3 = ConstantStandardXHeight
|
|
||||||
toEnum 4 = ConstantLargeXHeight
|
|
||||||
toEnum 5 = DuckingSmallXHeight
|
|
||||||
toEnum 6 = DuckingStandardXHeight
|
|
||||||
toEnum 7 = DuckingLargeXHeight
|
|
||||||
toEnum _ = error "Unknown X height"
|
|
||||||
|
|
||||||
-- * Kern table
|
-- * Kern table
|
||||||
|
|
||||||
|
Loading…
x
Reference in New Issue
Block a user