aboutsummaryrefslogtreecommitdiff
path: root/src/ZeroBin.hs
blob: d7bfc5cdc5a0c8d7b2f4a18102ae54cf9df89321 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
{-# LANGUAGE DeriveGeneric #-}

module ZeroBin (
  Expiration(..),
  pasteEc,
  share
) where

import Data.ByteString (ByteString)
import Data.ByteString.Base64 (encode)
import Data.Maybe (fromJust)
import GHC.Generics (Generic)
import ZeroBin.SJCL (encrypt, Content)
import ZeroBin.Utils (makePassword)
import qualified Data.Aeson as JSON
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Lazy as L
import qualified Network.HTTP.Conduit as HTTP

pasteEc :: String
pasteEc = "https://paste.ec"

data Response = Response {
    status  :: String
  , message :: Maybe String
  , paste   :: Maybe String
  } deriving (Generic, Show)
instance JSON.FromJSON Response

data Expiration
  = Once 
  | Day
  | Week
  | Month
  | Never

instance Show Expiration where
  show Once  = "burn_after_reading"
  show Day   = "1_day"
  show Week  = "1_week"
  show Month = "1_month"
  show Never = "never"

post :: Expiration -> Content -> IO Response
post ex ct = do
  req' <- HTTP.parseUrl $ pasteEc ++ "/paste/create"
  let req = HTTP.urlEncodedBody
            [ (C.pack "expiration" , C.pack     $ show ex)
            , (C.pack "content"    , L.toStrict $ JSON.encode ct)
            ] (req' { HTTP.secure = True })
  manager <- HTTP.newManager HTTP.tlsManagerSettings
  response <- HTTP.httpLbs req manager
  return . fromJust . JSON.decode $ HTTP.responseBody response

share :: Expiration -> ByteString -> IO (Either String String)
share ex txt = do 
  pwd  <- makePassword 33
  c    <- encrypt pwd (encode txt)
  resp <- post ex c
  case status resp of
    "ok" -> return . Right $
            pasteEc ++ "/paste/" ++ (fromJust . paste) resp ++ "#" ++ pwd
    _    -> return . Left $
            (fromJust . message) resp