{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies          #-}
module Waargonaut.Types.Whitespace
  (
    Whitespace (..)
  , WS (..)
  , _WhitespaceChar
  , escapedWhitespaceChar
  , unescapedWhitespaceChar
  , oneWhitespace
  , parseWhitespace
  , parseSomeWhitespace
  ) where
import           Control.Applicative     (liftA2)
import           Control.Lens            (AsEmpty (..), Cons (..), Prism',
                                          Rewrapped, Wrapped (..), iso,
                                          mapped, nearly, over, prism, prism',
                                          to, uncons, (^.), _2, _Wrapped)
import           Control.Lens.Extras     (is)
import           Data.Vector             (Vector)
import qualified Data.Vector             as V
import           Data.List.NonEmpty      (NonEmpty ((:|)))
import           Data.Foldable           (asum)
import           Data.Semigroup          (Semigroup (..))
import           Text.Parser.Char        (CharParsing, char, newline, tab)
import           Text.Parser.Combinators (many)
data Whitespace
  = Space
  | HorizontalTab
  | LineFeed
  | NewLine
  | CarriageReturn
  deriving (Eq, Ord, Show)
newtype WS = WS (Vector Whitespace)
  deriving (Eq, Show)
instance Cons WS WS Whitespace Whitespace where
  _Cons = prism' (\(w,ws) -> over _Wrapped (V.cons w) ws) (\(WS ws) -> over (mapped . _2) WS (uncons ws))
  {-# INLINE _Cons #-}
instance AsEmpty WS where
  _Empty = nearly mempty (^. _Wrapped . to (is _Empty))
  {-# INLINE _Empty #-}
instance WS ~ t => Rewrapped WS t
instance Wrapped WS where
  type Unwrapped WS = Vector Whitespace
  _Wrapped' = iso (\(WS x) -> x) WS
  {-# INLINE _Wrapped' #-}
instance Semigroup WS where
  (WS a) <> (WS b) = WS (a <> b)
  {-# INLINE (<>) #-}
instance Monoid WS where
  mempty = WS V.empty
  {-# INLINE mempty #-}
  mappend = (<>)
  {-# INLINE mappend #-}
_WhitespaceChar :: Prism' Char Whitespace
_WhitespaceChar = prism escapedWhitespaceChar
  (\x -> case x of
      ' '  -> Right Space
      '\t' -> Right HorizontalTab
      '\f' -> Right LineFeed
      '\r' -> Right CarriageReturn
      '\n' -> Right NewLine
      _    -> Left x
      )
oneWhitespace
  :: CharParsing f
  => f Whitespace
oneWhitespace = asum
  [ Space          <$ char ' '
  , HorizontalTab  <$ tab
  , LineFeed       <$ char '\f'
  , CarriageReturn <$ char '\r'
  , NewLine        <$ newline
  ]
parseWhitespace
  :: CharParsing f
  => f WS
parseWhitespace =
  WS . V.fromList <$> many oneWhitespace
parseSomeWhitespace
  :: CharParsing f
  => f (NonEmpty Whitespace)
parseSomeWhitespace =
  liftA2 (:|) oneWhitespace (many oneWhitespace)
unescapedWhitespaceChar :: Whitespace -> Char
unescapedWhitespaceChar Space          = ' '
unescapedWhitespaceChar HorizontalTab  = 't'
unescapedWhitespaceChar LineFeed       = 'f'
unescapedWhitespaceChar CarriageReturn = 'r'
unescapedWhitespaceChar NewLine        = 'n'
{-# INLINE unescapedWhitespaceChar #-}
escapedWhitespaceChar :: Whitespace -> Char
escapedWhitespaceChar Space          = ' '
escapedWhitespaceChar HorizontalTab  = '\t'
escapedWhitespaceChar LineFeed       = '\f'
escapedWhitespaceChar CarriageReturn = '\r'
escapedWhitespaceChar NewLine        = '\n'
{-# INLINE escapedWhitespaceChar #-}