{-# LANGUAGE ScopedTypeVariables, OverloadedStrings, ViewPatterns, RecordWildCards, DeriveFunctor #-}
module General.Web(
    Input(..),
    Output(..), readInput, server, general_web_test
    ) where
import Network.Wai.Handler.Warp hiding (Port, Handle)
import Network.Wai.Handler.WarpTLS
import Action.CmdLine
import Network.Wai.Logger
import Network.Wai
import Control.DeepSeq
import Network.HTTP.Types (parseQuery, decodePathSegments)
import Network.HTTP.Types.Status
import qualified Data.Text as Text
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import Data.List.Extra
import Data.Aeson.Encoding
import Data.Char
import Data.String
import Data.Tuple.Extra
import Data.Maybe
import Data.Monoid
import System.FilePath
import Control.Exception.Extra
import System.Time.Extra
import General.Log
import General.Util
import Prelude
import qualified Data.ByteString.UTF8 as UTF8
data Input = Input
    {Input -> [String]
inputURL :: [String]
    ,Input -> [(String, String)]
inputArgs :: [(String, String)]
    } deriving (Input -> Input -> Bool
(Input -> Input -> Bool) -> (Input -> Input -> Bool) -> Eq Input
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Input -> Input -> Bool
$c/= :: Input -> Input -> Bool
== :: Input -> Input -> Bool
$c== :: Input -> Input -> Bool
Eq, Int -> Input -> ShowS
[Input] -> ShowS
Input -> String
(Int -> Input -> ShowS)
-> (Input -> String) -> ([Input] -> ShowS) -> Show Input
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Input] -> ShowS
$cshowList :: [Input] -> ShowS
show :: Input -> String
$cshow :: Input -> String
showsPrec :: Int -> Input -> ShowS
$cshowsPrec :: Int -> Input -> ShowS
Show)
readInput :: String -> Maybe Input
readInput :: String -> Maybe Input
readInput (String -> String -> (String, String)
forall a. Eq a => [a] -> [a] -> ([a], [a])
breakOn String
"?" -> (String
a,String
b)) =
  if ([String] -> Bool
badPath [String]
path Bool -> Bool -> Bool
|| [(String, String)] -> Bool
forall b. [(String, b)] -> Bool
badArgs [(String, String)]
args) then Maybe Input
forall a. Maybe a
Nothing else Input -> Maybe Input
forall a. a -> Maybe a
Just (Input -> Maybe Input) -> Input -> Maybe Input
forall a b. (a -> b) -> a -> b
$ [String] -> [(String, String)] -> Input
Input [String]
path [(String, String)]
args
  where
    path :: [String]
path = String -> [String]
parsePath String
a
    parsePath :: String -> [String]
parsePath = (Text -> String) -> [Text] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Text -> String
Text.unpack
              ([Text] -> [String]) -> (String -> [Text]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [Text]
decodePathSegments
              (ByteString -> [Text])
-> (String -> ByteString) -> String -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
BS.pack
    
    
    
    
    
    
    badPath :: [String] -> Bool
badPath = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any String -> Bool
forall (t :: * -> *). Foldable t => t Char -> Bool
badSegment ([String] -> Bool) -> ([String] -> [String]) -> [String] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"")
    badSegment :: t Char -> Bool
badSegment t Char
seg = (Char -> Bool) -> t Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'.') t Char
seg Bool -> Bool -> Bool
|| (Char -> Bool) -> t Char -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isPathSeparator t Char
seg
    args :: [(String, String)]
args = String -> [(String, String)]
parseArgs String
b
    parseArgs :: String -> [(String, String)]
parseArgs = ((ByteString, Maybe ByteString) -> (String, String))
-> [(ByteString, Maybe ByteString)] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
map (ByteString -> String
UTF8.toString (ByteString -> String)
-> (Maybe ByteString -> String)
-> (ByteString, Maybe ByteString)
-> (String, String)
forall a a' b b'. (a -> a') -> (b -> b') -> (a, b) -> (a', b')
*** String -> (ByteString -> String) -> Maybe ByteString -> String
forall b a. b -> (a -> b) -> Maybe a -> b
maybe String
"" ByteString -> String
UTF8.toString)
              ([(ByteString, Maybe ByteString)] -> [(String, String)])
-> (String -> [(ByteString, Maybe ByteString)])
-> String
-> [(String, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [(ByteString, Maybe ByteString)]
parseQuery
              (ByteString -> [(ByteString, Maybe ByteString)])
-> (String -> ByteString)
-> String
-> [(ByteString, Maybe ByteString)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ByteString
UTF8.fromString
    badArgs :: [(String, b)] -> Bool
badArgs = Bool -> Bool
not (Bool -> Bool) -> ([(String, b)] -> Bool) -> [(String, b)] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, b) -> Bool) -> [(String, b)] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isLower (String -> Bool) -> ((String, b) -> String) -> (String, b) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, b) -> String
forall a b. (a, b) -> a
fst)
data Output
    = OutputText LBS.ByteString
    | OutputHTML LBS.ByteString
    | OutputJavascript LBS.ByteString
    | OutputJSON Encoding
    | OutputFail LBS.ByteString
    | OutputFile FilePath
      deriving Int -> Output -> ShowS
[Output] -> ShowS
Output -> String
(Int -> Output -> ShowS)
-> (Output -> String) -> ([Output] -> ShowS) -> Show Output
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Output] -> ShowS
$cshowList :: [Output] -> ShowS
show :: Output -> String
$cshow :: Output -> String
showsPrec :: Int -> Output -> ShowS
$cshowsPrec :: Int -> Output -> ShowS
Show
forceBS :: Output -> LBS.ByteString
forceBS :: Output -> ByteString
forceBS (OutputText ByteString
x) = ByteString -> ByteString
forall a. NFData a => a -> a
force ByteString
x
forceBS (OutputJSON Encoding
x) = ByteString -> ByteString
forall a. NFData a => a -> a
force (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Encoding -> ByteString
forall a. Encoding' a -> ByteString
encodingToLazyByteString Encoding
x
forceBS (OutputHTML ByteString
x) = ByteString -> ByteString
forall a. NFData a => a -> a
force ByteString
x
forceBS (OutputJavascript ByteString
x) = ByteString -> ByteString
forall a. NFData a => a -> a
force ByteString
x
forceBS (OutputFail ByteString
x) = ByteString -> ByteString
forall a. NFData a => a -> a
force ByteString
x
forceBS (OutputFile String
x) = String -> ()
forall a. NFData a => a -> ()
rnf String
x () -> ByteString -> ByteString
`seq` ByteString
LBS.empty
instance NFData Output where
    rnf :: Output -> ()
rnf Output
x = Output -> ByteString
forceBS Output
x ByteString -> () -> ()
`seq` ()
server :: Log -> CmdLine -> (Input -> IO Output) -> IO ()
server :: Log -> CmdLine -> (Input -> IO Output) -> IO ()
server Log
log Server{Bool
Int
String
Maybe String
Language
no_security_headers :: CmdLine -> Bool
datadir :: CmdLine -> Maybe String
key :: CmdLine -> String
cert :: CmdLine -> String
https :: CmdLine -> Bool
host :: CmdLine -> String
home :: CmdLine -> String
scope :: CmdLine -> String
links :: CmdLine -> Bool
local :: CmdLine -> Bool
logs :: CmdLine -> String
cdn :: CmdLine -> String
port :: CmdLine -> Int
haddock :: CmdLine -> Maybe String
language :: CmdLine -> Language
database :: CmdLine -> String
no_security_headers :: Bool
datadir :: Maybe String
key :: String
cert :: String
https :: Bool
host :: String
home :: String
scope :: String
language :: Language
links :: Bool
haddock :: Maybe String
local :: Bool
logs :: String
cdn :: String
database :: String
port :: Int
..} Input -> IO Output
act = do
    let
        host' :: HostPreference
host' = String -> HostPreference
forall a. IsString a => String -> a
fromString (String -> HostPreference) -> String -> HostPreference
forall a b. (a -> b) -> a -> b
$
                  if String
host String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"" then
                    if Bool
local then
                      String
"127.0.0.1"
                    else
                      String
"*"
                  else
                    String
host
        set :: Settings
set = (SomeException -> Response) -> Settings -> Settings
setOnExceptionResponse SomeException -> Response
exceptionResponseForDebug
            (Settings -> Settings)
-> (Settings -> Settings) -> Settings -> Settings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HostPreference -> Settings -> Settings
setHost HostPreference
host'
            (Settings -> Settings)
-> (Settings -> Settings) -> Settings -> Settings
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Settings -> Settings
setPort Int
port (Settings -> Settings) -> Settings -> Settings
forall a b. (a -> b) -> a -> b
$
            Settings
defaultSettings
        runServer :: Application -> IO ()
        runServer :: Application -> IO ()
runServer = if Bool
https then TLSSettings -> Settings -> Application -> IO ()
runTLS (String -> String -> TLSSettings
tlsSettings String
cert String
key) Settings
set
                             else Settings -> Application -> IO ()
runSettings Settings
set
        secH :: [(HeaderName, ByteString)]
secH = if Bool
no_security_headers then []
                                      else [
             
             (HeaderName
"Content-Security-Policy",
              
              
              
              ByteString
"default-src 'self';"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" script-src 'self' https://code.jquery.com/ https://rawcdn.githack.com;"
              
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" style-src 'self' 'unsafe-inline' https://rawcdn.githack.com;"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" img-src 'self' https://rawcdn.githack.com;"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" frame-ancestors 'self';"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" form-action 'self';"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" upgrade-insecure-requests;"
              
              
              ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" block-all-mixed-content"),
             
             
             
             
             (HeaderName
"X-Frame-Options", ByteString
"sameorigin"),
             
             
             
             
             
             (HeaderName
"X-Content-Type-Options", ByteString
"nosniff"),
             
             
             
             
             (HeaderName
"X-XSS-Protection", ByteString
"1; mode=block"),
             
             
             
             
             (HeaderName
"Referrer-Policy", ByteString
"no-referrer-when-downgrade"),
             
             
             
             
             
             
             (HeaderName
"Strict-Transport-Security", ByteString
"max-age=31536000; includeSubDomains")]
    Log -> String -> IO ()
logAddMessage Log
log (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Server starting on port " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
port String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" and host/IP " String -> ShowS
forall a. [a] -> [a] -> [a]
++ HostPreference -> String
forall a. Show a => a -> String
show HostPreference
host'
    Application -> IO ()
runServer (Application -> IO ()) -> Application -> IO ()
forall a b. (a -> b) -> a -> b
$ \Request
req Response -> IO ResponseReceived
reply -> do
        let pq :: String
pq = ByteString -> String
BS.unpack (ByteString -> String) -> ByteString -> String
forall a b. (a -> b) -> a -> b
$ Request -> ByteString
rawPathInfo Request
req ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Request -> ByteString
rawQueryString Request
req
        String -> IO ()
putStrLn String
pq
        (Seconds
time, Either String (Output, ByteString)
res) <- IO (Either String (Output, ByteString))
-> IO (Seconds, Either String (Output, ByteString))
forall (m :: * -> *) a. MonadIO m => m a -> m (Seconds, a)
duration (IO (Either String (Output, ByteString))
 -> IO (Seconds, Either String (Output, ByteString)))
-> IO (Either String (Output, ByteString))
-> IO (Seconds, Either String (Output, ByteString))
forall a b. (a -> b) -> a -> b
$ case String -> Maybe Input
readInput String
pq of
            Maybe Input
Nothing -> Either String (Output, ByteString)
-> IO (Either String (Output, ByteString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String (Output, ByteString)
 -> IO (Either String (Output, ByteString)))
-> Either String (Output, ByteString)
-> IO (Either String (Output, ByteString))
forall a b. (a -> b) -> a -> b
$ (Output, ByteString) -> Either String (Output, ByteString)
forall a b. b -> Either a b
Right (ByteString -> Output
OutputFail ByteString
"", String -> ByteString
LBS.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ String
"Bad URL: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pq)
            Just Input
pay ->
                (SomeException -> IO (Either String (Output, ByteString)))
-> IO (Either String (Output, ByteString))
-> IO (Either String (Output, ByteString))
forall a. (SomeException -> IO a) -> IO a -> IO a
handle_ ((String -> Either String (Output, ByteString))
-> IO String -> IO (Either String (Output, ByteString))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> Either String (Output, ByteString)
forall a b. a -> Either a b
Left (IO String -> IO (Either String (Output, ByteString)))
-> (SomeException -> IO String)
-> SomeException
-> IO (Either String (Output, ByteString))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> IO String
forall e. Show e => e -> IO String
showException) (IO (Either String (Output, ByteString))
 -> IO (Either String (Output, ByteString)))
-> IO (Either String (Output, ByteString))
-> IO (Either String (Output, ByteString))
forall a b. (a -> b) -> a -> b
$ do
                    Output
s <- Input -> IO Output
act Input
pay; ByteString
bs <- ByteString -> IO ByteString
forall a. a -> IO a
evaluate (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Output -> ByteString
forceBS Output
s; Either String (Output, ByteString)
-> IO (Either String (Output, ByteString))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either String (Output, ByteString)
 -> IO (Either String (Output, ByteString)))
-> Either String (Output, ByteString)
-> IO (Either String (Output, ByteString))
forall a b. (a -> b) -> a -> b
$ (Output, ByteString) -> Either String (Output, ByteString)
forall a b. b -> Either a b
Right (Output
s, ByteString
bs)
        Log -> String -> String -> Seconds -> Maybe String -> IO ()
logAddEntry Log
log (SockAddr -> String
showSockAddr (SockAddr -> String) -> SockAddr -> String
forall a b. (a -> b) -> a -> b
$ Request -> SockAddr
remoteHost Request
req) String
pq Seconds
time ((String -> Maybe String)
-> ((Output, ByteString) -> Maybe String)
-> Either String (Output, ByteString)
-> Maybe String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either String -> Maybe String
forall a. a -> Maybe a
Just (Maybe String -> (Output, ByteString) -> Maybe String
forall a b. a -> b -> a
const Maybe String
forall a. Maybe a
Nothing) Either String (Output, ByteString)
res)
        case Either String (Output, ByteString)
res of
            Left String
s -> Response -> IO ResponseReceived
reply (Response -> IO ResponseReceived)
-> Response -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status500 [] (ByteString -> Response) -> ByteString -> Response
forall a b. (a -> b) -> a -> b
$ String -> ByteString
LBS.pack String
s
            Right (Output
v, ByteString
bs) -> Response -> IO ResponseReceived
reply (Response -> IO ResponseReceived)
-> Response -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ case Output
v of
                OutputFile String
file -> Status
-> [(HeaderName, ByteString)]
-> String
-> Maybe FilePart
-> Response
responseFile Status
status200
                    ([(HeaderName
"content-type",ByteString
c) | Just ByteString
c <- [String -> [(String, ByteString)] -> Maybe ByteString
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (ShowS
takeExtension String
file) [(String, ByteString)]
contentType]] [(HeaderName, ByteString)]
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. [a] -> [a] -> [a]
++ [(HeaderName, ByteString)]
secH) String
file Maybe FilePart
forall a. Maybe a
Nothing
                OutputText{} -> Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status200 ((HeaderName
"content-type",ByteString
"text/plain") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: [(HeaderName, ByteString)]
secH) ByteString
bs
                OutputJSON{} -> Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status200 ((HeaderName
"content-type",ByteString
"application/json") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: (HeaderName
"access-control-allow-origin",ByteString
"*") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: [(HeaderName, ByteString)]
secH) ByteString
bs
                OutputFail{} -> Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status400 ((HeaderName
"content-type",ByteString
"text/plain") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: [(HeaderName, ByteString)]
secH) ByteString
bs
                OutputHTML{} -> Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status200 ((HeaderName
"content-type",ByteString
"text/html") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: [(HeaderName, ByteString)]
secH) ByteString
bs
                OutputJavascript{} -> Status -> [(HeaderName, ByteString)] -> ByteString -> Response
responseLBS Status
status200 ((HeaderName
"content-type",ByteString
"text/javascript") (HeaderName, ByteString)
-> [(HeaderName, ByteString)] -> [(HeaderName, ByteString)]
forall a. a -> [a] -> [a]
: [(HeaderName, ByteString)]
secH) ByteString
bs
contentType :: [(String, ByteString)]
contentType = [(String
".html",ByteString
"text/html"),(String
".css",ByteString
"text/css"),(String
".js",ByteString
"text/javascript")]
general_web_test :: IO ()
general_web_test :: IO ()
general_web_test = do
    String -> IO () -> IO ()
testing String
"General.Web.readInput" (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
        let b
a === :: b -> b -> IO ()
=== b
b = if b
a b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
b then Char -> IO ()
putChar Char
'.' else String -> IO ()
forall a. Partial => String -> IO a
errorIO (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ (b, b) -> String
forall a. Show a => a -> String
show (b
a,b
b)
        String -> Maybe Input
readInput String
"abc" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Input -> Maybe Input
forall a. a -> Maybe a
Just ([String] -> [(String, String)] -> Input
Input [String
"abc"] [])
        String -> Maybe Input
readInput String
"/abc" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Input -> Maybe Input
forall a. a -> Maybe a
Just ([String] -> [(String, String)] -> Input
Input [String
"abc"] [])
        String -> Maybe Input
readInput String
"/abc/" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Input -> Maybe Input
forall a. a -> Maybe a
Just ([String] -> [(String, String)] -> Input
Input [String
"abc", String
""] [])
        String -> Maybe Input
readInput String
"abc?ab=cd&ef=gh" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Input -> Maybe Input
forall a. a -> Maybe a
Just ([String] -> [(String, String)] -> Input
Input [String
"abc"] [(String
"ab", String
"cd"), (String
"ef", String
"gh")])
        String -> Maybe Input
readInput String
"%2fabc" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"%2F" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"def%2fabc" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"." Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
".." Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"..a" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Input -> Maybe Input
forall a. a -> Maybe a
Just ([String] -> [(String, String)] -> Input
Input [String
"..a"] [])
        String -> Maybe Input
readInput String
"../a" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"a/../a" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"%2e" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing
        String -> Maybe Input
readInput String
"%2E" Maybe Input -> Maybe Input -> IO ()
forall b. (Eq b, Show b) => b -> b -> IO ()
=== Maybe Input
forall a. Maybe a
Nothing