1 {-# LANGUAGE GeneralisedNewtypeDeriving #-}
3 module Webc.Decoder where
5 import Control.Applicative (Applicative (..))
6 import Control.Monad (Monad (..))
7 import Control.Monad.Trans.Class qualified as MT
8 import Control.Monad.Trans.Except qualified as MT
9 import Control.Monad.Trans.State qualified as MT
10 import Data.Bifunctor (first)
12 import Data.Either (Either (..))
13 import Data.Eq (Eq (..))
14 import Data.Foldable (null)
15 import Data.Function (($), (.))
16 import Data.Functor (Functor, (<$>))
18 import Network.URI.Slug
19 import Symantic.Classes (Iso (..), IsoFunctor ((<%>)), ProductFunctor (..), SumFunctor ((<+>)))
20 import Text.Show (Show)
24 -- * The 'Decoder' interpreter
26 -- | A very very basic parser.
27 newtype Decoder a = Decoder
31 (MT.Except DecoderError)
34 deriving (Functor, Applicative)
36 decode :: Decoder a -> [Slug] -> Either DecoderError a
37 decode (Decoder dec) slugs = case MT.runExcept (MT.runStateT dec slugs) of
41 | otherwise -> Left $ DecoderErrorLeftover st
44 = DecoderErrorMismatch {expectedSlug :: Slug, gotSlug :: Slug}
46 | DecoderErrorLeftover [Slug]
47 deriving (Eq, Ord, Show)
49 instance IsoFunctor Decoder where
50 (<%>) Iso{..} = (a2b <$>)
51 instance ProductFunctor Decoder where
55 instance SumFunctor Decoder where
56 Decoder x <+> Decoder y = Decoder $
58 case MT.runExcept $ MT.runStateT x st of
59 Right (a, st') -> return (Left a, st')
61 -- TODO: better error merging
62 case MT.runExcept $ MT.runStateT y st of
63 Right (b, st') -> return (Right b, st')
64 Left err -> MT.throwE err
65 instance Repeatable Decoder where
66 many0 (Decoder x) = Decoder (MT.StateT (return . go))
69 case MT.runExcept $ MT.runStateT x st of
70 Left _err -> ([], st) -- always backtrack
71 Right (a, st') -> first (a :) (go st')
72 many1 x = (:) <$> x <*> many0 x
73 instance Slugable Decoder where
74 literalSlug expectedSlug = Decoder $ do
77 [] -> MT.lift $ MT.throwE DecoderErrorMissing
79 | expectedSlug /= gotSlug ->
80 MT.lift $ MT.throwE $ DecoderErrorMismatch{..}
81 | otherwise -> MT.put nextSlugs
82 captureSlug _name = Decoder $ do
85 [] -> MT.lift $ MT.throwE DecoderErrorMissing
86 gotSlug : nextSlugs -> do