module MSGraphAPI.Files.DriveItem (
listRootChildrenMe
, listGroupItemChildren
, downloadFile
, downloadFileMe
, DriveItem(..)
, DIItem(..)
, File(..), Folder(..), Package(..)
) where
import Control.Applicative (Alternative(..))
import Data.Int (Int32)
import GHC.Generics (Generic(..))
import qualified Data.Aeson as A (ToJSON(..), FromJSON(..), genericParseJSON, (.:), Object, withObject, Key)
import qualified Data.Aeson.Types as A (Parser)
import qualified Data.ByteString.Lazy as LBS (ByteString)
import Network.OAuth.OAuth2.Internal (AccessToken(..))
import Network.HTTP.Req (Req)
import Data.Text (Text)
import Data.Time (ZonedTime)
import qualified MSGraphAPI.Internal.Common as MSG (get, getLbs, Collection, aesonOptions)
data DriveItem = DriveItem {
DriveItem -> Text
diId :: Text
, DriveItem -> Text
diName :: Text
, DriveItem -> ZonedTime
diLastModifiedDateTime :: ZonedTime
, DriveItem -> DIItem
diItem :: DIItem
} deriving (Int -> DriveItem -> ShowS
[DriveItem] -> ShowS
DriveItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DriveItem] -> ShowS
$cshowList :: [DriveItem] -> ShowS
show :: DriveItem -> String
$cshow :: DriveItem -> String
showsPrec :: Int -> DriveItem -> ShowS
$cshowsPrec :: Int -> DriveItem -> ShowS
Show, forall x. Rep DriveItem x -> DriveItem
forall x. DriveItem -> Rep DriveItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DriveItem x -> DriveItem
$cfrom :: forall x. DriveItem -> Rep DriveItem x
Generic)
instance A.ToJSON DriveItem
instance A.FromJSON DriveItem where
parseJSON :: Value -> Parser DriveItem
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
A.withObject String
"DriveItem" forall a b. (a -> b) -> a -> b
$ \Object
o -> Text -> Text -> ZonedTime -> DIItem -> DriveItem
DriveItem forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"id" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"name" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"lastModifiedDateTime" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Object -> Parser DIItem
diItemP Object
o
diItemP :: A.Object -> A.Parser DIItem
diItemP :: Object -> Parser DIItem
diItemP Object
o =
(File -> DIItem
DIIFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"file") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(Folder -> DIItem
DIIFolder forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"folder") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(DIItem
DIIRemoteItem forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Object
o Object -> Key -> Parser ()
.: Key
"remoteItem") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(DIItem
DIIPhoto forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Object
o Object -> Key -> Parser ()
.: Key
"photo") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(DIItem
DIIVideo forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Object
o Object -> Key -> Parser ()
.: Key
"video") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(DIItem
DIIBundle forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Object
o Object -> Key -> Parser ()
.: Key
"bundle") forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
(Package -> DIItem
DIIPackage forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o forall a. FromJSON a => Object -> Key -> Parser a
A..: Key
"package")
(.:) :: A.Object -> A.Key -> A.Parser ()
.: :: Object -> Key -> Parser ()
(.:) = forall a. FromJSON a => Object -> Key -> Parser a
(A..:)
data DIItem = DIIFile File
| DIIFolder Folder
| DIIRemoteItem
| DIIPhoto
| DIIVideo
| DIIBundle
| DIIPackage Package
deriving (DIItem -> DIItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DIItem -> DIItem -> Bool
$c/= :: DIItem -> DIItem -> Bool
== :: DIItem -> DIItem -> Bool
$c== :: DIItem -> DIItem -> Bool
Eq, Eq DIItem
DIItem -> DIItem -> Bool
DIItem -> DIItem -> Ordering
DIItem -> DIItem -> DIItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DIItem -> DIItem -> DIItem
$cmin :: DIItem -> DIItem -> DIItem
max :: DIItem -> DIItem -> DIItem
$cmax :: DIItem -> DIItem -> DIItem
>= :: DIItem -> DIItem -> Bool
$c>= :: DIItem -> DIItem -> Bool
> :: DIItem -> DIItem -> Bool
$c> :: DIItem -> DIItem -> Bool
<= :: DIItem -> DIItem -> Bool
$c<= :: DIItem -> DIItem -> Bool
< :: DIItem -> DIItem -> Bool
$c< :: DIItem -> DIItem -> Bool
compare :: DIItem -> DIItem -> Ordering
$ccompare :: DIItem -> DIItem -> Ordering
Ord, Int -> DIItem -> ShowS
[DIItem] -> ShowS
DIItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DIItem] -> ShowS
$cshowList :: [DIItem] -> ShowS
show :: DIItem -> String
$cshow :: DIItem -> String
showsPrec :: Int -> DIItem -> ShowS
$cshowsPrec :: Int -> DIItem -> ShowS
Show, forall x. Rep DIItem x -> DIItem
forall x. DIItem -> Rep DIItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DIItem x -> DIItem
$cfrom :: forall x. DIItem -> Rep DIItem x
Generic)
instance A.ToJSON DIItem where
toJSON :: DIItem -> Value
toJSON = \case
DIIFile File
f -> forall a. ToJSON a => a -> Value
A.toJSON File
f
DIIFolder Folder
f -> forall a. ToJSON a => a -> Value
A.toJSON Folder
f
DIIPackage Package
f -> forall a. ToJSON a => a -> Value
A.toJSON Package
f
DIItem
e -> forall a. ToJSON a => a -> Value
A.toJSON forall a b. (a -> b) -> a -> b
$ forall a. Int -> [a] -> [a]
drop Int
3 (forall a. Show a => a -> String
show DIItem
e)
data Folder = Folder {
Folder -> Int32
difoChildCount :: Int32
} deriving (Folder -> Folder -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Folder -> Folder -> Bool
$c/= :: Folder -> Folder -> Bool
== :: Folder -> Folder -> Bool
$c== :: Folder -> Folder -> Bool
Eq, Eq Folder
Folder -> Folder -> Bool
Folder -> Folder -> Ordering
Folder -> Folder -> Folder
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Folder -> Folder -> Folder
$cmin :: Folder -> Folder -> Folder
max :: Folder -> Folder -> Folder
$cmax :: Folder -> Folder -> Folder
>= :: Folder -> Folder -> Bool
$c>= :: Folder -> Folder -> Bool
> :: Folder -> Folder -> Bool
$c> :: Folder -> Folder -> Bool
<= :: Folder -> Folder -> Bool
$c<= :: Folder -> Folder -> Bool
< :: Folder -> Folder -> Bool
$c< :: Folder -> Folder -> Bool
compare :: Folder -> Folder -> Ordering
$ccompare :: Folder -> Folder -> Ordering
Ord, Int -> Folder -> ShowS
[Folder] -> ShowS
Folder -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Folder] -> ShowS
$cshowList :: [Folder] -> ShowS
show :: Folder -> String
$cshow :: Folder -> String
showsPrec :: Int -> Folder -> ShowS
$cshowsPrec :: Int -> Folder -> ShowS
Show, forall x. Rep Folder x -> Folder
forall x. Folder -> Rep Folder x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Folder x -> Folder
$cfrom :: forall x. Folder -> Rep Folder x
Generic)
instance A.FromJSON Folder where
parseJSON :: Value -> Parser Folder
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSG.aesonOptions String
"difo")
instance A.ToJSON Folder
data File = File {
File -> Text
difiMimeType :: Text
} deriving (File -> File -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: File -> File -> Bool
$c/= :: File -> File -> Bool
== :: File -> File -> Bool
$c== :: File -> File -> Bool
Eq, Eq File
File -> File -> Bool
File -> File -> Ordering
File -> File -> File
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: File -> File -> File
$cmin :: File -> File -> File
max :: File -> File -> File
$cmax :: File -> File -> File
>= :: File -> File -> Bool
$c>= :: File -> File -> Bool
> :: File -> File -> Bool
$c> :: File -> File -> Bool
<= :: File -> File -> Bool
$c<= :: File -> File -> Bool
< :: File -> File -> Bool
$c< :: File -> File -> Bool
compare :: File -> File -> Ordering
$ccompare :: File -> File -> Ordering
Ord, Int -> File -> ShowS
[File] -> ShowS
File -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [File] -> ShowS
$cshowList :: [File] -> ShowS
show :: File -> String
$cshow :: File -> String
showsPrec :: Int -> File -> ShowS
$cshowsPrec :: Int -> File -> ShowS
Show, forall x. Rep File x -> File
forall x. File -> Rep File x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep File x -> File
$cfrom :: forall x. File -> Rep File x
Generic)
instance A.FromJSON File where
parseJSON :: Value -> Parser File
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSG.aesonOptions String
"difi")
instance A.ToJSON File
data Package = Package {
Package -> Text
dipType :: Text
} deriving (Package -> Package -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Package -> Package -> Bool
$c/= :: Package -> Package -> Bool
== :: Package -> Package -> Bool
$c== :: Package -> Package -> Bool
Eq, Eq Package
Package -> Package -> Bool
Package -> Package -> Ordering
Package -> Package -> Package
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Package -> Package -> Package
$cmin :: Package -> Package -> Package
max :: Package -> Package -> Package
$cmax :: Package -> Package -> Package
>= :: Package -> Package -> Bool
$c>= :: Package -> Package -> Bool
> :: Package -> Package -> Bool
$c> :: Package -> Package -> Bool
<= :: Package -> Package -> Bool
$c<= :: Package -> Package -> Bool
< :: Package -> Package -> Bool
$c< :: Package -> Package -> Bool
compare :: Package -> Package -> Ordering
$ccompare :: Package -> Package -> Ordering
Ord, Int -> Package -> ShowS
[Package] -> ShowS
Package -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Package] -> ShowS
$cshowList :: [Package] -> ShowS
show :: Package -> String
$cshow :: Package -> String
showsPrec :: Int -> Package -> ShowS
$cshowsPrec :: Int -> Package -> ShowS
Show, forall x. Rep Package x -> Package
forall x. Package -> Rep Package x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Package x -> Package
$cfrom :: forall x. Package -> Rep Package x
Generic)
instance A.FromJSON Package where
parseJSON :: Value -> Parser Package
parseJSON = forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
A.genericParseJSON (String -> Options
MSG.aesonOptions String
"dip")
instance A.ToJSON Package
downloadFileMe :: Text
-> AccessToken -> Req LBS.ByteString
downloadFileMe :: Text -> AccessToken -> Req ByteString
downloadFileMe Text
itemId = [Text] -> Option 'Https -> AccessToken -> Req ByteString
MSG.getLbs [Text
"me", Text
"drive", Text
"items", Text
itemId, Text
"content"] forall a. Monoid a => a
mempty
downloadFile :: Text
-> Text
-> AccessToken -> Req LBS.ByteString
downloadFile :: Text -> Text -> AccessToken -> Req ByteString
downloadFile Text
did Text
itemId = [Text] -> Option 'Https -> AccessToken -> Req ByteString
MSG.getLbs [Text
"drives", Text
did, Text
"items", Text
itemId, Text
"content"] forall a. Monoid a => a
mempty
listRootChildrenMe :: AccessToken -> Req (MSG.Collection DriveItem)
listRootChildrenMe :: AccessToken -> Req (Collection DriveItem)
listRootChildrenMe = forall a.
FromJSON a =>
[Text] -> Option 'Https -> AccessToken -> Req a
MSG.get [Text
"me", Text
"drive", Text
"root", Text
"children"] forall a. Monoid a => a
mempty
listGroupItemChildren :: Text
-> Text
-> AccessToken -> Req (MSG.Collection DriveItem)
listGroupItemChildren :: Text -> Text -> AccessToken -> Req (Collection DriveItem)
listGroupItemChildren Text
gid Text
iid =
forall a.
FromJSON a =>
[Text] -> Option 'Https -> AccessToken -> Req a
MSG.get [Text
"groups", Text
gid, Text
"drive", Text
"items", Text
iid, Text
"children"] forall a. Monoid a => a
mempty