]> gitweb @ CieloNegro.org - Lucu.git/commitdiff
Data.URI has been moved to https://github.com/phonohawk/extensible-uri router
authorPHO <pho@cielonegro.org>
Fri, 13 Jan 2012 03:46:45 +0000 (12:46 +0900)
committerPHO <pho@cielonegro.org>
Fri, 13 Jan 2012 03:46:45 +0000 (12:46 +0900)
Data/URI.hs [deleted file]
Data/URI/Internal.hs [deleted file]
Data/URI/Internal/Scheme.hs [deleted file]
Lucu.cabal

diff --git a/Data/URI.hs b/Data/URI.hs
deleted file mode 100644 (file)
index c55a55f..0000000
+++ /dev/null
@@ -1,6 +0,0 @@
--- |FIXME
-module Data.URI
-    ( Scheme
-    )
-    where
-import Data.URI.Internal.Scheme
diff --git a/Data/URI/Internal.hs b/Data/URI/Internal.hs
deleted file mode 100644 (file)
index ffb8a7b..0000000
+++ /dev/null
@@ -1,37 +0,0 @@
-{-# 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
diff --git a/Data/URI/Internal/Scheme.hs b/Data/URI/Internal/Scheme.hs
deleted file mode 100644 (file)
index ebef877..0000000
+++ /dev/null
@@ -1,84 +0,0 @@
-{-# LANGUAGE
-    DeriveDataTypeable
-  , FlexibleInstances
-  , GeneralizedNewtypeDeriving
-  , MultiParamTypeClasses
-  , StandaloneDeriving
-  , TemplateHaskell
-  , TypeSynonymInstances
-  , UnicodeSyntax
-  #-}
-module Data.URI.Internal.Scheme
-    ( Scheme
-    )
-    where
-import Data.Ascii (AsciiBuilder, 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,
--- digits, plus (\'+\'), period (\'.\'), or hyphen (\'-\'). Comparison
--- of 'Scheme's are always case-insensitive. See:
--- <http://tools.ietf.org/html/rfc3986#section-3.1>
-newtype Scheme = Scheme CIAscii
-    deriving ( Eq
-             , FoldCase
-             , Hashable
-             , Ord
-             , Show
-             , Typeable
-             )
-
--- |'fromString' is a fast but unsafe way to create 'Scheme' such that
--- no validation on the string is performed.
-deriving instance IsString 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 ∨
-                isDigit c       ∨
-                c ≡ '+'         ∨
-                c ≡ '-'         ∨
-                c ≡ '.'
-          {-# INLINE fromBS #-}
-          fromBS = Scheme ∘ A.toCIAscii ∘ A.unsafeFromByteString
-
--- |Extract a 'CIAscii' with all letters lowercased.
-instance ConvertSuccess Scheme CIAscii where
-    {-# INLINE convertSuccess #-}
-    convertSuccess (Scheme s) = foldCase s
-
--- |Create an 'AsciiBuilder' with all letters lowercased.
-instance ConvertSuccess Scheme AsciiBuilder where
-    {-# INLINE convertSuccess #-}
-    convertSuccess = A.toAsciiBuilder ∘ A.fromCIAscii ∘ cs
-
--- |Try to parse a 'Scheme' from 'CIAscii'.
-instance ConvertAttempt CIAscii Scheme where
-    {-# INLINE convertAttempt #-}
-    convertAttempt = parseAttempt' def ∘ A.fromCIAscii
-
-deriveAttempts [ ([t| Scheme |], [t| AsciiBuilder |])
-               , ([t| Scheme |], [t| CIAscii      |])
-               ]
index 2778a2a2c0201d6df08198e056c9125f5bc083b1..a3f7e1d18817e1f717f72bfe9f1b6b492733ff78 100644 (file)
@@ -37,7 +37,7 @@ Extra-Source-Files:
     examples/small-file.txt
 
 Source-Repository head
-    Type: git
+    Type:     git
     Location: git://git.cielonegro.org/Lucu.git
 
 Flag build-lucu-implant-file
@@ -69,7 +69,6 @@ Library
         data-default               == 0.3.*,
         directory                  == 1.1.*,
         filepath                   == 1.2.*,
-        hashable                   == 1.1.*,
         mtl                        == 2.0.*,
         network                    == 2.3.*,
         old-time                   == 1.0.*,
@@ -90,7 +89,6 @@ Library
             -DHAVE_SSL
 
     Exposed-Modules:
-        Data.URI
         Data.Collections.Newtype.TH
         Network.HTTP.Lucu
         Network.HTTP.Lucu.Abortion
@@ -122,8 +120,6 @@ Library
         Network.HTTP.Lucu.Utils
 
     Other-Modules:
-        Data.URI.Internal
-        Data.URI.Internal.Scheme
         Network.HTTP.Lucu.Abortion.Internal
         Network.HTTP.Lucu.Chunk
         Network.HTTP.Lucu.ContentCoding