{-# LANGUAGE OverloadedStrings #-}
module Network.PublicSuffixList.Lookup (effectiveTLDPlusOne, effectiveTLDPlusOne', isSuffix, isSuffix') where
import qualified Data.Map as M
import Data.Maybe (isNothing)
import qualified Data.Text as T
import qualified Network.PublicSuffixList.DataStructure as DS
import Network.PublicSuffixList.Types
{-|
OffEnd's Bool argument represents whether we fell off a
leaf or whether we fell off a non-leaf. True means that
we fell off a leaf. Its Text argument is the component
that pushed us off the end, along with all the components
to the right of that one, interspersed with "."s
-}
data LookupResult = Inside | AtLeaf | OffEndBoolT.Textderiving (Eq){-|
This function returns whether or not this domain is owned by a
registrar or a regular person. 'Nothing' means that this is a registrar
domain; 'Just x' means it's owned by a person. This is used to determine
if a cookie is allowed to bet set for a particular domain. For
example, you shouldn't be able to set a cookie for \"com\".
If the value is 'Just x', then the x value is what is known as the
effective TLD plus one. This is one segment more than the suffix of the
domain. For example, the eTLD+1 for "this.is.a.subdom.com" is Just
"subdom.com"
Note that this function expects lowercase ASCII strings. These strings
should be gotten from the toASCII algorithm as described in RFC 3490.
These strings should not start or end with the \'.\' character, and should
not have two \'.\' characters next to each other.
(The toASCII algorithm is implemented in the \'idna\' hackage package,
though that package doesn't always map strings to lowercase)
-}effectiveTLDPlusOne' :: DataStructure -> T.Text -> MaybeT.TexteffectiveTLDPlusOne'dataStructures-- Any TLD is a suffix
| lengthss==1 = Nothing
| otherwise = outputrulesResultexceptionResult
where ss = T.splitOn"."sps = reversessexceptionResult = recurseps [] $snddataStructurerulesResult = recurseps [] $fstdataStructure-- If we fell off, did we do it at a leaf? Otherwise, what's the-- subtree that we're atgetNext :: TreeT.Text -> T.Text -> EitherBool (TreeT.Text)
getNextts' = case M.lookups'$childrent of
Nothing -> Left (M.null$childrent)
Justt' -> Rightt'getNextWithStarts' = case getNextts' of
Left _ -> getNextt"*"r -> rrecurse :: [T.Text] -> [T.Text] -> TreeT.Text -> LookupResultrecurse [] _ t
| M.null$childrent = AtLeaf
| otherwise = Insiderecurse (c:cs) prevt = case getNextWithStartc of
Leftb -> OffEndb$T.intercalate"." (c:prev)
Rightt' -> recursecs (c:prev) t'-- Only match against the exception rules if we have a full matchoutput _ AtLeaf = Justsoutput _ (OffEndTruex) = Just$T.intercalate"."$tail$T.splitOn"."x-- If we have a subdomain on an existing rule, we're not a suffixoutput (OffEnd _ x) _
-- A single level domain can never be a eTLD+1
| isNothing$T.find (=='.') x = Just$T.intercalate"."$drop (lengthss-2) ss
| otherwise = Justx-- Otherwise, we're a suffix of a suffix, which is a suffixoutput _ _ = Nothing-- | >>> effectiveTLDPlusOne = effectiveTLDPlusOne' Network.PublicSuffixList.DataStructure.dataStructureeffectiveTLDPlusOne :: T.Text -> MaybeT.TexteffectiveTLDPlusOne = effectiveTLDPlusOne'DS.dataStructure-- | >>> isSuffix' dataStructure = isNothing . effectiveTLDPlusOne' dataStructureisSuffix' :: DataStructure -> T.Text -> BoolisSuffix'dataStructure = isNothing.effectiveTLDPlusOne'dataStructure-- | >>> isSuffix = isSuffix' Network.PublicSuffixList.DataStructure.dataStructureisSuffix :: T.Text -> BoolisSuffix = isNothing.effectiveTLDPlusOne