{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.Database.Admin.Types.Hyperdata.Frame
where
import Control.Lens
import Data.ByteString.Lazy (toStrict)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
import Gargantext.Prelude
import Gargantext.Database.Admin.Types.Hyperdata.Prelude
import qualified Network.Wreq as Wreq
data HyperdataFrame =
HyperdataFrame { HyperdataFrame -> Text
_hf_base :: !Text
, HyperdataFrame -> Text
_hf_frame_id :: !Text
}
deriving ((forall x. HyperdataFrame -> Rep HyperdataFrame x)
-> (forall x. Rep HyperdataFrame x -> HyperdataFrame)
-> Generic HyperdataFrame
forall x. Rep HyperdataFrame x -> HyperdataFrame
forall x. HyperdataFrame -> Rep HyperdataFrame x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HyperdataFrame x -> HyperdataFrame
$cfrom :: forall x. HyperdataFrame -> Rep HyperdataFrame x
Generic, Int -> HyperdataFrame -> ShowS
[HyperdataFrame] -> ShowS
HyperdataFrame -> String
(Int -> HyperdataFrame -> ShowS)
-> (HyperdataFrame -> String)
-> ([HyperdataFrame] -> ShowS)
-> Show HyperdataFrame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HyperdataFrame] -> ShowS
$cshowList :: [HyperdataFrame] -> ShowS
show :: HyperdataFrame -> String
$cshow :: HyperdataFrame -> String
showsPrec :: Int -> HyperdataFrame -> ShowS
$cshowsPrec :: Int -> HyperdataFrame -> ShowS
Show)
defaultHyperdataFrame :: HyperdataFrame
defaultHyperdataFrame :: HyperdataFrame
defaultHyperdataFrame = Text -> Text -> HyperdataFrame
HyperdataFrame Text
"" Text
""
instance Hyperdata HyperdataFrame
makeLenses ''HyperdataFrame
$(deriveJSON (unPrefix "_hf_") ''HyperdataFrame)
instance Arbitrary HyperdataFrame where
arbitrary :: Gen HyperdataFrame
arbitrary = HyperdataFrame -> Gen HyperdataFrame
forall (f :: * -> *) a. Applicative f => a -> f a
pure HyperdataFrame
defaultHyperdataFrame
instance FromField HyperdataFrame
where
fromField :: FieldParser HyperdataFrame
fromField = FieldParser HyperdataFrame
forall b.
(Typeable b, FromJSON b) =>
Field -> Maybe ByteString -> Conversion b
fromField'
instance DefaultFromField PGJsonb HyperdataFrame
where
defaultFromField :: FromField PGJsonb HyperdataFrame
defaultFromField = FromField PGJsonb HyperdataFrame
forall haskell pgType.
FromField haskell =>
FromField pgType haskell
fieldQueryRunnerColumn
instance ToSchema HyperdataFrame where
declareNamedSchema :: Proxy HyperdataFrame -> Declare (Definitions Schema) NamedSchema
declareNamedSchema Proxy HyperdataFrame
proxy =
SchemaOptions
-> Proxy HyperdataFrame -> Declare (Definitions Schema) NamedSchema
forall a.
(Generic a, GToSchema (Rep a),
TypeHasSimpleShape a "genericDeclareNamedSchemaUnrestricted") =>
SchemaOptions
-> Proxy a -> Declare (Definitions Schema) NamedSchema
genericDeclareNamedSchema (String -> SchemaOptions
unPrefixSwagger String
"_hf_") Proxy HyperdataFrame
proxy
Declare (Definitions Schema) NamedSchema
-> (Declare (Definitions Schema) NamedSchema
-> Declare (Definitions Schema) NamedSchema)
-> Declare (Definitions Schema) NamedSchema
forall a b. a -> (a -> b) -> b
& (NamedSchema -> Identity NamedSchema)
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema)
forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped((NamedSchema -> Identity NamedSchema)
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema))
-> ((Maybe Text -> Identity (Maybe Text))
-> NamedSchema -> Identity NamedSchema)
-> (Maybe Text -> Identity (Maybe Text))
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Schema -> Identity Schema) -> NamedSchema -> Identity NamedSchema
forall s a. HasSchema s a => Lens' s a
schema((Schema -> Identity Schema)
-> NamedSchema -> Identity NamedSchema)
-> ((Maybe Text -> Identity (Maybe Text))
-> Schema -> Identity Schema)
-> (Maybe Text -> Identity (Maybe Text))
-> NamedSchema
-> Identity NamedSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe Text -> Identity (Maybe Text)) -> Schema -> Identity Schema
forall s a. HasDescription s a => Lens' s a
description ((Maybe Text -> Identity (Maybe Text))
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema))
-> Text
-> Declare (Definitions Schema) NamedSchema
-> Declare (Definitions Schema) NamedSchema
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Text
"Frame Hyperdata"
Declare (Definitions Schema) NamedSchema
-> (Declare (Definitions Schema) NamedSchema
-> Declare (Definitions Schema) NamedSchema)
-> Declare (Definitions Schema) NamedSchema
forall a b. a -> (a -> b) -> b
& (NamedSchema -> Identity NamedSchema)
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema)
forall (f :: * -> *) a b. Functor f => Setter (f a) (f b) a b
mapped((NamedSchema -> Identity NamedSchema)
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema))
-> ((Maybe Value -> Identity (Maybe Value))
-> NamedSchema -> Identity NamedSchema)
-> (Maybe Value -> Identity (Maybe Value))
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Schema -> Identity Schema) -> NamedSchema -> Identity NamedSchema
forall s a. HasSchema s a => Lens' s a
schema((Schema -> Identity Schema)
-> NamedSchema -> Identity NamedSchema)
-> ((Maybe Value -> Identity (Maybe Value))
-> Schema -> Identity Schema)
-> (Maybe Value -> Identity (Maybe Value))
-> NamedSchema
-> Identity NamedSchema
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe Value -> Identity (Maybe Value))
-> Schema -> Identity Schema
forall s a. HasExample s a => Lens' s a
example ((Maybe Value -> Identity (Maybe Value))
-> Declare (Definitions Schema) NamedSchema
-> Identity (Declare (Definitions Schema) NamedSchema))
-> Value
-> Declare (Definitions Schema) NamedSchema
-> Declare (Definitions Schema) NamedSchema
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ HyperdataFrame -> Value
forall a. ToJSON a => a -> Value
toJSON HyperdataFrame
defaultHyperdataFrame
getHyperdataFrameContents :: HyperdataFrame -> IO Text
getHyperdataFrameContents :: HyperdataFrame -> IO Text
getHyperdataFrameContents (HyperdataFrame { Text
_hf_base :: Text
_hf_base :: HyperdataFrame -> Text
_hf_base, Text
_hf_frame_id :: Text
_hf_frame_id :: HyperdataFrame -> Text
_hf_frame_id }) = do
let path :: Text
path = [Text] -> Text
T.concat [Text
_hf_base, Text
"/", Text
_hf_frame_id, Text
"/download"]
Response ByteString
r <- String -> IO (Response ByteString)
Wreq.get (String -> IO (Response ByteString))
-> String -> IO (Response ByteString)
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
path
Text -> IO Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Response ByteString
r Response ByteString
-> Getting ByteString (Response ByteString) ByteString
-> ByteString
forall s a. s -> Getting a s a -> a
^. Getting ByteString (Response ByteString) ByteString
forall body0 body1.
Lens (Response body0) (Response body1) body0 body1
Wreq.responseBody
getHyperdataFrameCSV :: HyperdataFrame -> IO Text
getHyperdataFrameCSV :: HyperdataFrame -> IO Text
getHyperdataFrameCSV (HyperdataFrame { Text
_hf_base :: Text
_hf_base :: HyperdataFrame -> Text
_hf_base, Text
_hf_frame_id :: Text
_hf_frame_id :: HyperdataFrame -> Text
_hf_frame_id }) = do
let path :: Text
path = [Text] -> Text
T.concat [Text
_hf_base, Text
"/", Text
_hf_frame_id, Text
".csv"]
Response ByteString
r <- String -> IO (Response ByteString)
Wreq.get (String -> IO (Response ByteString))
-> String -> IO (Response ByteString)
forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
path
Text -> IO Text
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> IO Text) -> Text -> IO Text
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
decodeUtf8 (ByteString -> Text) -> ByteString -> Text
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Response ByteString
r Response ByteString
-> Getting ByteString (Response ByteString) ByteString
-> ByteString
forall s a. s -> Getting a s a -> a
^. Getting ByteString (Response ByteString) ByteString
forall body0 body1.
Lens (Response body0) (Response body1) body0 body1
Wreq.responseBody