--- /dev/null
+Copyright (c) 2009 George Pollard
+
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions
+are met:
+
+1. Redistributions of source code must retain the above copyright
+ notice, this list of conditions and the following disclaimer.
+
+2. Redistributions in binary form must reproduce the above copyright
+ notice, this list of conditions and the following disclaimer in the
+ documentation and/or other materials provided with the distribution.
+
+3. Neither the name of the author nor the names of his contributors
+ may be used to endorse or promote products derived from this software
+ without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND ANY EXPRESS OR
+IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
+WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
+DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR
+ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
+DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
+OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
+HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
+STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+POSSIBILITY OF SUCH DAMAGE.
--- /dev/null
+{-# LANGUAGE OverloadedStrings #-}
+-- | This module implements the two algorithms from RFC 3490. (<http://tools.ietf.org/html/rfc3490>)
+module Text.IDNA (acePrefix, toASCII, toUnicode)
+where
+
+import Text.StringPrep
+import Text.StringPrep.Profiles
+import qualified Data.Text as Text
+import Data.Text (Text)
+import qualified Data.Text.Punycode as Puny
+import Data.Text.Encoding as E
+
+-- | The ASCII Compatible Encoding prefix (currently \'@xn--@\').
+acePrefix :: Text
+acePrefix = "xn--"
+
+-- | Implements the ToASCII algorithm.
+toASCII :: Bool -- ^ Whether to allow unassigned code points (in RFC: AllowUnassigned).
+ -> Bool -- ^ Whether to disallow certain ASCII characters (in RFC: UseSTD3ASCIIRules).
+ -> Text -- ^ The text to transform.
+ -> Maybe Text
+toASCII allowUnassigned useSTD3ASCIIRules t = do
+ step2 <- if Text.any (>'\x7f') t
+ then runStringPrep (namePrepProfile allowUnassigned) t
+ else return t
+
+ step3 <- if (useSTD3ASCIIRules && (Text.any isLDHascii step2 || Text.head step2 == '-' || Text.last step2 == '-'))
+ then Nothing
+ else return step2
+
+ step7 <- if (Text.any (>'\x7f') step2)
+ then if acePrefix `Text.isPrefixOf` step3
+ then Nothing
+ else case return (Puny.encode step3) of -- TODO: this can fail?
+ Left _ -> Nothing
+ Right t' -> return $ acePrefix `Text.append` E.decodeUtf8 t'
+ else return step3
+
+ if Text.length step7 <= 63
+ then return step7
+ else Nothing
+
+isLDHascii :: Char -> Bool
+isLDHascii c =
+ '\x0' <= c && c <= '\x2c' ||
+ '\x2e' <= c && c <= '\x2f' ||
+ '\x3a' <= c && c <= '\x40' ||
+ '\x5b' <= c && c <= '\x60' ||
+ '\x7b' <= c && c <= '\x7f'
+
+toUnicode :: Bool -- ^ Whether to allow unassigned code points (in RFC: AllowUnassigned).
+ -> Bool -- ^ Whether to disallow certain ASCII characters (in RFC: UseSTD3ASCIIRules).
+ -> Text -- ^ The text to transform.
+ -> Text
+toUnicode allowUnassigned useSTD3ASCIIRules t = mergeEither $ do
+ step2 <- if Text.any (>'\x7f') t
+ then case runStringPrep (namePrepProfile allowUnassigned) t of
+ Nothing -> Left t
+ Just t' -> return t'
+ else return t
+
+ step3 <- if not $ acePrefix `Text.isPrefixOf` step2
+ then Left step2
+ else return step2
+
+ let step4 = Text.drop (Text.length acePrefix) step3
+ step5 <- case Puny.decode $ E.encodeUtf8 step4 of
+ Left _ -> Left step3
+ Right s -> return s
+
+ case toASCII allowUnassigned useSTD3ASCIIRules step5 of
+ Nothing -> return step3
+ Just t' -> if t' == step3
+ then return step5
+ else return step3
+
+mergeEither :: Either a a -> a
+mergeEither (Left x) = x
+mergeEither (Right y) = y
+
+tests :: [Text]
+tests = ["Bücher","tūdaliņ"]
--- /dev/null
+Name: idna
+Version: 0.3.0
+Description: Implements IDNA - Internationalized Domain Names in Applications (RFC 3490).
+Synopsis: Implements IDNA (RFC 3490).
+License: BSD3
+Author: George Pollard <porges@porg.es>
+Maintainer: George Pollard <porges@porg.es>
+Build-Type: Simple
+Cabal-Version: >=1.6
+License-file: LICENSE
+Category: Data, Text, RFC
+
+Library
+ Build-Depends: base >= 4.3 && < 5, stringprep >=1 && < 2, text>=0.1, punycode>=2.0
+ Exposed-modules: Text.IDNA
+ ghc-options: -O2 -Wall
+
+source-repository head
+ type: git
+ location: https://github.com/Porges/idna-hs.git
+
+source-repository this
+ type: git
+ location: https://github.com/Porges/idna-hs.git
+ tag: v0.3.0