module Text.ShellEscape.Sh where
import Data.ByteString (ByteString)
import Text.ShellEscape.Escape
import qualified Text.ShellEscape.Put as Put
import Text.ShellEscape.EscapeVector
newtype Sh                   =  Sh (EscapeVector EscapingMode)
 deriving (Eq, Ord, Show)
sh                          ::  ByteString -> Sh
sh                           =  escape
instance Escape Sh where
  escape                     =  Sh . escWith classify
  unescape (Sh v)            =  stripEsc v
  bytes (Sh v)               =  interpretEsc v act finish ([], Literal)
   where
    finish Quote             =  Put.putChar '\''
    finish Backslash         =  Put.putChar '\\'
    finish Literal           =  return ()
act :: EscapingMode -> (Char, EscapingMode) -> (Put.Put, EscapingMode)
act Quote (c, Quote)         =  (Put.putChar c                 , Quote)
act Quote (c, Literal)       =  (Put.putChar c                 , Quote)
act Quote (c, Backslash)     =  (Put.putString ['\'', '\\', c] , Literal)
act Backslash (c, Backslash) =  (Put.putChar c                 , Literal)
act Backslash (c, Quote)     =  (Put.putString ['\\', '\'', c] , Quote)
act Backslash (c, Literal)   =  (Put.putString ['\\', c]       , Literal)
act Literal (c, Literal)     =  (Put.putChar c                 , Literal)
act Literal (c, Backslash)   =  (Put.putString ['\\', c]       , Literal)
act Literal (c, Quote)       =  (Put.putString ['\'', c]       , Quote)
classify                    ::  Char -> EscapingMode
classify c | c <= '&'        =  Quote           
           | c == '\''       =  Backslash       
           | c <= ','        =  Quote           
           | c <= '9'        =  Literal         
           | c <= '?'        =  Quote           
           | c <= 'Z'        =  Literal         
           | c <= '^'        =  Quote           
           | c == '_'        =  Literal         
           | c == '`'        =  Quote           
           | c <= 'z'        =  Literal         
           | c <= '\DEL'     =  Quote           
           | otherwise       =  Quote           
data EscapingMode            =  Backslash | Literal | Quote
 deriving (Eq, Ord, Show)