{-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE OverloadedStrings #-} module Descript.Lex.Data.Atom ( Symbol (..) , Prim (..) , codeSym , codeLangSym , codeContentSym , undefinedSym , primExt , encodePrim ) where import Descript.Misc import Data.Semigroup import Data.Text (Text) import qualified Data.Text.Encoding as Text import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as ByteString -- | An identifier. Used to distinguish records and record properties. data Symbol an = Symbol { symbolAnn :: an , symbolLiteral :: String } deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) -- | A built-in primitive. A piece of data in code not represented by a record. -- -- In Descript, most values are typically represented by records. While -- /theoretically/ every value /could/ be a record, converting some -- values like strings and numbers is verbose and inefficient. -- -- Currently, the only primitives are numbers and strings. In the -- future, images and other arbitrary data could be added. data Prim an = PrimNumber an Rational | PrimText an Text deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable) instance Ann Symbol where getAnn = symbolAnn instance EAnn Symbol where Symbol xKeyAnn xKeyStr `eappend` Symbol yKeyAnn yKeyStr | xKeyStr /= yKeyStr = error "Symbols have different content" | otherwise = Symbol (xKeyAnn <> yKeyAnn) xKeyStr instance Ann Prim where getAnn (PrimNumber ann _) = ann getAnn (PrimText ann _) = ann instance Printable Symbol where aprint (Symbol _ str) = plex str instance Printable Prim where aprint (PrimNumber _ num) = pprim num aprint (PrimText _ str) = pprim str instance (Show an) => Summary (Symbol an) where summary = pprintSummary instance (Show an) => Summary (Prim an) where summary = pprintSummary -- | The record head for code blocks. codeSym :: Symbol () codeSym = Symbol () "Code" -- | The property key for a code block's language codeLangSym :: Symbol () codeLangSym = Symbol () "lang" -- | The property key for a code block's content. codeContentSym :: Symbol () codeContentSym = Symbol () "content" -- | A symbol for an undefined value - e.g. an unresolved implicit -- property. undefinedSym :: Symbol () undefinedSym = Symbol () "{undefined}" -- | The extension of a file with the given primitive. primExt :: Prim () -> String primExt _ = "txt" -- So far everything is just text. -- | Write a primitive into a 'ByteString'. Just encodes the underlying -- number or string. encodePrim :: Prim () -> ByteString encodePrim (PrimNumber () x) = ByteString.pack $ show x encodePrim (PrimText () x) = Text.encodeUtf8 x