{-# LANGUAGE DefaultSignatures, FlexibleContexts, FlexibleInstances, TypeFamilies,
TypeSynonymInstances, UndecidableInstances #-}
module Construct.Classes where
import qualified Rank2
import qualified Text.ParserCombinators.Incremental as Incremental
import Control.Applicative (Alternative ((<|>), empty))
import qualified Data.Attoparsec.ByteString as Attoparsec
import Text.Parser.Input (InputParsing (ParserInput))
class Alternative m => AlternativeFail m where
failure :: String -> m a
expectedName :: String -> m a -> m a
failure = const empty
expectedName = const id
class InputMappableParsing m where
mapParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') =>
(s -> s') -> (s' -> s) -> m s a -> m s' a
mapMaybeParserInput :: (InputParsing (m s), s ~ ParserInput (m s), Monoid s, Monoid s') =>
(s -> Maybe s') -> (s' -> Maybe s) -> m s a -> m s' a
class Monad m => FixTraversable m where
fixSequence :: (Rank2.Traversable g, Applicative n) => g m -> m (g n)
fixSequence = Rank2.traverse (pure <$>)
data Error = Error [String] (Maybe String) deriving (Eq, Show)
instance Semigroup Error where
Error expected1 encountered1 <> Error expected2 encountered2 =
Error (expected1 <> expected2) (maybe encountered2 Just encountered1)
instance AlternativeFail Maybe
instance AlternativeFail []
instance {-# OVERLAPS #-} Alternative (Either Error) where
empty = Left (Error [] Nothing)
Right a <|> _ = Right a
_ <|> Right a = Right a
Left e1 <|> Left e2 = Left (e1 <> e2)
instance AlternativeFail (Either Error) where
failure encountered = Left (Error [] (Just encountered))
expectedName expected (Left (Error _ encountered)) = Left (Error [expected] encountered)
expectedName _ success = success
errorString :: Error -> String
errorString (Error ex Nothing) = maybe "" ("expected " <>) (concatExpected ex)
errorString (Error [] (Just en)) = "encountered " <> en
errorString (Error ex (Just en)) = maybe "" ("expected " <>) (concatExpected ex) <> ", encountered " <> en
concatExpected :: [String] -> Maybe String
concatExpected [] = Nothing
concatExpected [e] = Just e
concatExpected [e1, e2] = Just (e1 <> " or " <> e2)
concatExpected (e:es) = Just (oxfordComma e es)
oxfordComma :: String -> [String] -> String
oxfordComma e [] = "or " <> e
oxfordComma e (e':es) = e <> ", " <> oxfordComma e' es
instance FixTraversable Attoparsec.Parser
instance Monoid s => FixTraversable (Incremental.Parser t s) where
fixSequence = Incremental.record
instance InputMappableParsing (Incremental.Parser t) where
mapParserInput = Incremental.mapInput
mapMaybeParserInput = Incremental.mapMaybeInput