{-# 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
data LookupResult = Inside | AtLeaf | OffEnd Bool T.Text
  deriving (LookupResult -> LookupResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LookupResult -> LookupResult -> Bool
$c/= :: LookupResult -> LookupResult -> Bool
== :: LookupResult -> LookupResult -> Bool
$c== :: LookupResult -> LookupResult -> Bool
Eq)
effectiveTLDPlusOne' :: DataStructure -> T.Text -> Maybe T.Text
effectiveTLDPlusOne' :: DataStructure -> Text -> Maybe Text
effectiveTLDPlusOne' DataStructure
dataStructure Text
s
  
  | forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
ss forall a. Eq a => a -> a -> Bool
== Int
1 = forall a. Maybe a
Nothing
  | Bool
otherwise = LookupResult -> LookupResult -> Maybe Text
output LookupResult
rulesResult LookupResult
exceptionResult
  where ss :: [Text]
ss = Text -> Text -> [Text]
T.splitOn Text
"." Text
s
        ps :: [Text]
ps = forall a. [a] -> [a]
reverse [Text]
ss
        exceptionResult :: LookupResult
exceptionResult = [Text] -> [Text] -> Tree Text -> LookupResult
recurse [Text]
ps [] forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd DataStructure
dataStructure
        rulesResult :: LookupResult
rulesResult = [Text] -> [Text] -> Tree Text -> LookupResult
recurse [Text]
ps [] forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> a
fst DataStructure
dataStructure
        
        
        getNext :: Tree T.Text -> T.Text -> Either Bool (Tree T.Text)
        getNext :: Tree Text -> Text -> Either Bool (Tree Text)
getNext Tree Text
t Text
s' = case forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
s' forall a b. (a -> b) -> a -> b
$ forall e. Tree e -> Map e (Tree e)
children Tree Text
t of
          Maybe (Tree Text)
Nothing -> forall a b. a -> Either a b
Left (forall k a. Map k a -> Bool
M.null forall a b. (a -> b) -> a -> b
$ forall e. Tree e -> Map e (Tree e)
children Tree Text
t)
          Just Tree Text
t' -> forall a b. b -> Either a b
Right Tree Text
t'
        
        getNextWithStar :: Tree Text -> Text -> Either Bool (Tree Text)
getNextWithStar Tree Text
t Text
s' = case Tree Text -> Text -> Either Bool (Tree Text)
getNext Tree Text
t Text
s' of
          
          Left Bool
_ -> Tree Text -> Text -> Either Bool (Tree Text)
getNext Tree Text
t Text
"*"
          Either Bool (Tree Text)
r -> Either Bool (Tree Text)
r
        recurse :: [T.Text] -> [T.Text] -> Tree T.Text -> LookupResult
        recurse :: [Text] -> [Text] -> Tree Text -> LookupResult
recurse [] [Text]
_ Tree Text
t
          | forall k a. Map k a -> Bool
M.null forall a b. (a -> b) -> a -> b
$ forall e. Tree e -> Map e (Tree e)
children Tree Text
t = LookupResult
AtLeaf
          | Bool
otherwise = LookupResult
Inside
        recurse (Text
c : [Text]
cs) [Text]
prev Tree Text
t = case Tree Text -> Text -> Either Bool (Tree Text)
getNextWithStar Tree Text
t Text
c of
          Left Bool
b -> Bool -> Text -> LookupResult
OffEnd Bool
b forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"." (Text
c forall a. a -> [a] -> [a]
: [Text]
prev)
          Right Tree Text
t' -> [Text] -> [Text] -> Tree Text -> LookupResult
recurse [Text]
cs (Text
c forall a. a -> [a] -> [a]
: [Text]
prev) Tree Text
t'
        
        output :: LookupResult -> LookupResult -> Maybe Text
output LookupResult
_ LookupResult
AtLeaf = forall a. a -> Maybe a
Just Text
s
        output LookupResult
_ (OffEnd Bool
True Text
x) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"." forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn Text
"." Text
x
        
        output (OffEnd Bool
_ Text
x) LookupResult
_
          
          | forall a. Maybe a -> Bool
isNothing forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Maybe Char
T.find (forall a. Eq a => a -> a -> Bool
== Char
'.') Text
x = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> [Text] -> Text
T.intercalate Text
"." forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
ss forall a. Num a => a -> a -> a
- Int
2) [Text]
ss
          | Bool
otherwise = forall a. a -> Maybe a
Just Text
x
        
        output LookupResult
_ LookupResult
_ = forall a. Maybe a
Nothing
effectiveTLDPlusOne :: T.Text -> Maybe T.Text
effectiveTLDPlusOne :: Text -> Maybe Text
effectiveTLDPlusOne = DataStructure -> Text -> Maybe Text
effectiveTLDPlusOne' DataStructure
DS.dataStructure
isSuffix' :: DataStructure -> T.Text -> Bool
isSuffix' :: DataStructure -> Text -> Bool
isSuffix' DataStructure
dataStructure = forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. DataStructure -> Text -> Maybe Text
effectiveTLDPlusOne' DataStructure
dataStructure
isSuffix :: T.Text -> Bool
isSuffix :: Text -> Bool
isSuffix = forall a. Maybe a -> Bool
isNothing forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text
effectiveTLDPlusOne