--- /dev/null
+{-# LANGUAGE
+ UnicodeSyntax
+ #-}
+module Data.URI.Internal
+ ( finishOff
+ , parseAttempt
+ , parseAttempt'
+ )
+ where
+import Control.Applicative
+import Control.Exception.Base
+import Control.Monad.Unicode
+import Data.Ascii (Ascii)
+import qualified Data.Ascii as A
+import Data.Attempt
+import Data.Attoparsec.Char8
+import Data.ByteString (ByteString)
+import Prelude.Unicode
+
+finishOff ∷ Parser α → Parser α
+{-# INLINE finishOff #-}
+finishOff = ((endOfInput *>) ∘ return =≪)
+
+parseAttempt ∷ Exception e
+ ⇒ (String → e)
+ → Parser α
+ → ByteString
+ → Attempt α
+{-# INLINEABLE parseAttempt #-}
+parseAttempt f p bs
+ = case parseOnly (finishOff p) bs of
+ Right α → Success α
+ Left e → Failure $ f e
+
+parseAttempt' ∷ Parser α → Ascii → Attempt α
+{-# INLINE parseAttempt' #-}
+parseAttempt' = (∘ A.toByteString) ∘ parseAttempt StringException
{-# LANGUAGE
DeriveDataTypeable
+ , FlexibleInstances
, GeneralizedNewtypeDeriving
+ , MultiParamTypeClasses
, StandaloneDeriving
+ , TemplateHaskell
+ , TypeSynonymInstances
, UnicodeSyntax
#-}
module Data.URI.Internal.Scheme
( Scheme
- , unsafeCreateScheme
)
where
import Data.Ascii (CIAscii)
+import qualified Data.Ascii as A
+import Data.Attoparsec.Char8
+import qualified Data.ByteString.Char8 as BS
import Data.CaseInsensitive
+import Data.Convertible.Base
+import Data.Default
import Data.Hashable
import Data.String
+import Data.URI.Internal
import Data.Typeable
+import Prelude hiding (takeWhile)
+import Prelude.Unicode
-- |'Scheme' names consist of a non-empty sequence of characters
-- beginning with a letter and followed by any combination of letters,
, Show
, Typeable
)
--- scheme = ALPHA *( ALPHA / DIGIT / "+" / "-" / "." )
-- |'isString' is a fast but unsafe way to create 'Scheme' such that
-- no validation on the string is performed.
deriving instance IsString Scheme
--- |Converts a 'CIAscii' to 'Scheme' without any validation on the
--- string.
-unsafeCreateScheme ∷ CIAscii → Scheme
-{-# INLINE CONLIKE unsafeCreateScheme #-}
-unsafeCreateScheme = Scheme
+instance Default (Parser Scheme) where
+ {-# INLINEABLE def #-}
+ def = do x ← satisfy first
+ xs ← takeWhile nonFirst
+ return ∘ fromBS $ x `BS.cons` xs
+ <?>
+ "scheme"
+ where
+ {-# INLINE first #-}
+ first = isAlpha_ascii
+ {-# INLINE nonFirst #-}
+ nonFirst c
+ = isAlpha_ascii c ∨
+ c ≡ '+' ∨
+ c ≡ '-' ∨
+ c ≡ '.'
+ {-# INLINE fromBS #-}
+ fromBS = Scheme ∘ A.toCIAscii ∘ A.unsafeFromByteString
+
+instance ConvertSuccess Scheme CIAscii where
+ {-# INLINE convertSuccess #-}
+ convertSuccess (Scheme s) = s
+
+instance ConvertAttempt CIAscii Scheme where
+ {-# INLINE convertAttempt #-}
+ convertAttempt = parseAttempt' def ∘ A.fromCIAscii
+
+deriveAttempts [ ([t| Scheme |], [t| CIAscii |])
+ ]