{-# OPTIONS_GHC -fno-warn-orphans #-}
module Text.Regex.PCRE.String(
  
  Regex,
  MatchOffset,
  MatchLength,
  CompOption(CompOption),
  ExecOption(ExecOption),
  ReturnCode,
  WrapError,
  
  unusedOffset,
  getVersion,
  
  compile,
  execute,
  regexec,
  
  compBlank,
  compAnchored,
  compAutoCallout,
  compCaseless,
  compDollarEndOnly,
  compDotAll,
  compExtended,
  compExtra,
  compFirstLine,
  compMultiline,
  compNoAutoCapture,
  compUngreedy,
  compUTF8,
  compNoUTF8Check,
  
  execBlank,
  execAnchored,
  execNotBOL,
  execNotEOL,
  execNotEmpty,
  execNoUTF8Check,
  execPartial
  ) where
import Prelude hiding (fail)
import Control.Monad.Fail (MonadFail(fail))
import Text.Regex.PCRE.Wrap 
import Foreign.C.String(withCStringLen,withCString)
import Data.Array(Array,listArray)
import System.IO.Unsafe(unsafePerformIO)
import Text.Regex.Base.RegexLike(RegexMaker(..),RegexLike(..),RegexContext(..),MatchLength,MatchOffset)
import Text.Regex.Base.Impl(polymatch,polymatchM)
instance RegexContext Regex String String where
  match = polymatch
  matchM = polymatchM
unwrap :: (Show e) => Either e v -> IO v
unwrap x = case x of Left err -> fail ("Text.Regex.PCRE.String died: "++ show err)
                     Right v -> return v
instance RegexMaker Regex CompOption ExecOption String where
  makeRegexOpts c e pattern = unsafePerformIO $
    compile c e pattern >>= unwrap
  makeRegexOptsM c e pattern = either (fail.show) return $ unsafePerformIO $
    compile c e pattern
instance RegexLike Regex String where
  matchTest regex str = unsafePerformIO $
    withCStringLen str (wrapTest 0 regex) >>= unwrap
  matchOnce regex str = unsafePerformIO $
    execute regex str >>= unwrap
  matchAll regex str = unsafePerformIO $
    withCStringLen str (wrapMatchAll regex) >>= unwrap
  matchCount regex str = unsafePerformIO $
    withCStringLen str (wrapCount regex) >>= unwrap
compile :: CompOption 
        -> ExecOption 
        -> String     
        -> IO (Either (MatchOffset,String) Regex) 
compile c e pattern = withCString pattern (wrapCompile c e)
execute :: Regex      
        -> String     
        -> IO (Either WrapError (Maybe (Array Int (MatchOffset,MatchLength))))
                
                
                
execute regex str = do
  maybeStartEnd <- withCStringLen str (wrapMatch 0 regex)
  case maybeStartEnd of
    Right Nothing -> return (Right Nothing)
    Right (Just parts) ->
      return . Right . Just . listArray (0,pred (length parts))
      . map (\(s,e)->(fromIntegral s, fromIntegral (e-s))) $ parts
    Left err -> return (Left err)
regexec  :: Regex      
         -> String     
         -> IO (Either WrapError (Maybe (String, String,String, [String])))
                      
                      
regexec regex str = do
  let getSub (start,stop) | start == unusedOffset = ""
                          | otherwise = take (stop-start) . drop start $ str
      matchedParts [] = ("","",str,[]) 
      matchedParts (matchedStartStop@(start,stop):subStartStop) =
        (take start str
        ,getSub matchedStartStop
        ,drop stop str
        ,map getSub subStartStop)
  maybeStartEnd <- withCStringLen str (wrapMatch 0 regex)
  case maybeStartEnd of
    Right Nothing -> return (Right Nothing)
    Right (Just parts) -> return . Right . Just . matchedParts $ parts
    Left err -> return (Left err)