Server: minor changes. Add Blob type for auto base64 decoding.

This commit is contained in:
John MacFarlane 2022-08-15 09:00:25 -07:00
parent 9d12fcb0c7
commit 5416c7f82d

View file

@ -23,27 +23,31 @@ import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TLE import qualified Data.Text.Lazy.Encoding as TLE
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.Char (isAlphaNum) import Data.Char (isAlphaNum)
import Data.ByteString.Lazy (fromStrict, toStrict) import Data.ByteString.Lazy (fromStrict, toStrict, ByteString)
import Data.ByteString.Base64 import Data.ByteString.Base64 (decodeBase64, encodeBase64)
import Data.Default import Data.Default
import Data.Set (Set) import Data.Set (Set)
import Skylighting (defaultSyntaxMap) import Skylighting (defaultSyntaxMap)
data FileSpec = FileSpec newtype Blob = Blob ByteString
{ path :: Text deriving (Show, Eq)
, contents :: Text
, base64 :: Maybe Bool
} deriving (Show)
-- Automatically derive code to convert to/from JSON. instance ToJSON Blob where
$(deriveJSON defaultOptions ''FileSpec) toJSON (Blob bs) = toJSON (encodeBase64 $ toStrict bs)
instance FromJSON Blob where
parseJSON = withText "Blob" $ \t -> do
let inp = UTF8.fromText t
case decodeBase64 inp of
Right bs -> return $ Blob $ fromStrict bs
Left _ -> -- treat as regular text
return $ Blob $ fromStrict inp
-- This is the data to be supplied by the JSON payload -- This is the data to be supplied by the JSON payload
-- of requests. Maybe values may be omitted and will be -- of requests. Maybe values may be omitted and will be
-- given default values. -- given default values.
data Params = Params data Params = Params
{ text :: Text { text :: Text
, files :: Maybe [FileSpec]
, from :: Maybe Text , from :: Maybe Text
, to :: Maybe Text , to :: Maybe Text
, wrapText :: Maybe WrapOption , wrapText :: Maybe WrapOption
@ -76,19 +80,19 @@ data Params = Params
, highlightStyle :: Maybe Text , highlightStyle :: Maybe Text
, setextHeaders :: Maybe Bool , setextHeaders :: Maybe Bool
, epubSubdirectory :: Maybe Text , epubSubdirectory :: Maybe Text
, epubMetadata :: Maybe Text
, epubFonts :: Maybe [FilePath] , epubFonts :: Maybe [FilePath]
, epubMetadata :: Maybe Text
, epubChapterLevel :: Maybe Int , epubChapterLevel :: Maybe Int
, tocDepth :: Maybe Int , tocDepth :: Maybe Int
, referenceDoc :: Maybe FilePath , referenceDoc :: Maybe FilePath
, referenceLocation :: Maybe ReferenceLocation , referenceLocation :: Maybe ReferenceLocation
, preferAscii :: Maybe Bool , preferAscii :: Maybe Bool
, files :: Maybe [(FilePath, Blob)]
} deriving (Show) } deriving (Show)
instance Default Params where instance Default Params where
def = Params def = Params
{ text = "" { text = ""
, files = Nothing
, from = Nothing , from = Nothing
, to = Nothing , to = Nothing
, wrapText = Nothing , wrapText = Nothing
@ -122,15 +126,15 @@ instance Default Params where
, setextHeaders = Nothing , setextHeaders = Nothing
, epubSubdirectory = Nothing , epubSubdirectory = Nothing
, epubMetadata = Nothing , epubMetadata = Nothing
, epubFonts = Nothing
, epubChapterLevel = Nothing , epubChapterLevel = Nothing
, epubFonts = Nothing
, tocDepth = Nothing , tocDepth = Nothing
, referenceDoc = Nothing , referenceDoc = Nothing
, referenceLocation = Nothing , referenceLocation = Nothing
, preferAscii = Nothing , preferAscii = Nothing
, files = Nothing
} }
-- TODO: -- TODO:
-- [ ] add files to common state
-- shiftHeadingLevelBy -- shiftHeadingLevelBy
-- metadata -- metadata
-- selfContained -- selfContained
@ -138,11 +142,7 @@ instance Default Params where
-- epubCoverImage -- epubCoverImage
-- stripEmptyParagraphs -- stripEmptyParagraphs
-- titlePrefix -- titlePrefix
-- css
-- ipynbOutput -- ipynbOutput
-- includeBeforeBody
-- includeAfterBody
-- includeInHeader
-- eol -- eol
-- csl -- csl
-- bibliography -- bibliography