Skip to content

Commit

Permalink
autoformat with fourmolu
Browse files Browse the repository at this point in the history
  • Loading branch information
chris-martin committed Jan 18, 2024
1 parent ef7dc44 commit fbdcd05
Show file tree
Hide file tree
Showing 9 changed files with 371 additions and 349 deletions.
72 changes: 37 additions & 35 deletions library/Asana/Api/CustomField.hs
Original file line number Diff line number Diff line change
@@ -1,15 +1,15 @@
module Asana.Api.CustomField
( CustomField(..)
, CustomFields(..)
, customEnumId
, EnumOption(..)
, putCustomField
, putCustomFields
) where

import Asana.Api.Prelude
( CustomField (..),
CustomFields (..),
customEnumId,
EnumOption (..),
putCustomField,
putCustomFields,
)
where

import Asana.Api.Gid (Gid, gidToText)
import Asana.Api.Prelude
import Asana.Api.Request
import Data.Aeson
import Data.Aeson.Casing (aesonPrefix, snakeCase)
Expand All @@ -22,27 +22,28 @@ data CustomField
= CustomNumber Gid Text (Maybe Scientific)
| CustomEnum Gid Text [EnumOption] (Maybe Text)
| CustomText Gid Text (Maybe Text)
| Other -- ^ Unexpected types dumped here
| -- | Unexpected types dumped here
Other
deriving stock (Eq, Generic, Show)

newtype CustomFields = CustomFields { getCustomFields :: [CustomField] }
newtype CustomFields = CustomFields {getCustomFields :: [CustomField]}
deriving stock (Show, Eq)
deriving newtype (FromJSON)

instance ToJSON CustomFields where
toJSON (CustomFields fields) = object $ concatMap toPair fields
where
toPair = \case
CustomNumber gid _ n -> [gidToKey gid .= n]
e@(CustomEnum gid _ _ _) -> [gidToKey gid .= customEnumId e]
_ -> []
where
toPair = \case
CustomNumber gid _ n -> [gidToKey gid .= n]
e@(CustomEnum gid _ _ _) -> [gidToKey gid .= customEnumId e]
_ -> []

-- fromString will give us Text for aeson-1.x and Key for aeson-2.x
gidToKey = fromString . T.unpack . gidToText
-- fromString will give us Text for aeson-1.x and Key for aeson-2.x
gidToKey = fromString . T.unpack . gidToText

data EnumOption = EnumOption
{ eoGid :: Gid
, eoName :: Text
{ eoGid :: Gid,
eoName :: Text
}
deriving stock (Eq, Generic, Show)

Expand All @@ -54,7 +55,6 @@ instance FromJSON EnumOption where
-- - Must be a @'CustomEnum'@
-- - Must have a value
-- - Must have an option with the same name as that value
--
customEnumId :: CustomField -> Maybe Gid
customEnumId (CustomEnum _ _ opts mValue) = do
value <- mValue
Expand All @@ -77,22 +77,24 @@ instance FromJSON CustomField where
<*> (o .: "name")
<*> (o .: "enum_options")
<*> case value of
Object vo -> vo .:? "name"
_ -> pure Nothing
Object vo -> vo .:? "name"
_ -> pure Nothing
_ -> pure Other

putCustomField
:: (MonadUnliftIO m, MonadLogger m, MonadReader env m, HasAsanaAccessKey env)
=> Gid
-> CustomField
-> m ()
putCustomField ::
(MonadUnliftIO m, MonadLogger m, MonadReader env m, HasAsanaAccessKey env) =>
Gid ->
CustomField ->
m ()
putCustomField taskId = putCustomFields taskId . CustomFields . pure

putCustomFields
:: (MonadUnliftIO m, MonadLogger m, MonadReader env m, HasAsanaAccessKey env)
=> Gid
-> CustomFields
-> m ()
putCustomFields ::
(MonadUnliftIO m, MonadLogger m, MonadReader env m, HasAsanaAccessKey env) =>
Gid ->
CustomFields ->
m ()
putCustomFields taskId fields =
void $ put ("/tasks/" <> T.unpack (gidToText taskId)) $ ApiData
(object ["custom_fields" .= fields])
void $
put ("/tasks/" <> T.unpack (gidToText taskId)) $
ApiData
(object ["custom_fields" .= fields])
23 changes: 14 additions & 9 deletions library/Asana/Api/Gid.hs
Original file line number Diff line number Diff line change
@@ -1,24 +1,29 @@
-- | A globally unique identifier
module Asana.Api.Gid
( Gid
, AsanaReference(..)
, gidToText
, textToGid
) where
( Gid,
AsanaReference (..),
gidToText,
textToGid,
)
where

import Asana.Api.Prelude

import Data.Aeson
(FromJSON(..), FromJSONKey, ToJSON, ToJSONKey, genericParseJSON)
( FromJSON (..),
FromJSONKey,
ToJSON,
ToJSONKey,
genericParseJSON,
)
import Data.Aeson.Casing (aesonPrefix, snakeCase)
import Data.Hashable (Hashable)

newtype Gid = Gid { gidToText :: Text }
newtype Gid = Gid {gidToText :: Text}
deriving stock (Eq, Generic, Show)
deriving newtype (FromJSON, ToJSON, ToJSONKey, FromJSONKey, Hashable)

-- | An object @{ gid: <Gid> }@
newtype AsanaReference = AsanaReference { arGid :: Gid }
newtype AsanaReference = AsanaReference {arGid :: Gid}
deriving stock (Eq, Generic, Show)

instance FromJSON AsanaReference where
Expand Down
12 changes: 6 additions & 6 deletions library/Asana/Api/Named.hs
Original file line number Diff line number Diff line change
@@ -1,17 +1,17 @@
-- | Anything with a compact @{ id, name }@ representation
module Asana.Api.Named
( Named(..)
) where

import Asana.Api.Prelude
( Named (..),
)
where

import Asana.Api.Gid (Gid)
import Asana.Api.Prelude
import Data.Aeson (FromJSON, genericParseJSON, parseJSON)
import Data.Aeson.Casing (aesonPrefix, snakeCase)

data Named = Named
{ nGid :: Gid
, nName :: Text
{ nGid :: Gid,
nName :: Text
}
deriving stock (Eq, Generic, Show)

Expand Down
18 changes: 12 additions & 6 deletions library/Asana/Api/Prelude.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
module Asana.Api.Prelude
( module X
) where

import Prelude as X
( module X,
)
where

import Control.Arrow as X ((&&&), (***))
import Control.Monad.IO.Unlift as X (MonadUnliftIO)
Expand All @@ -12,11 +11,18 @@ import Data.Bifunctor as X (first, second)
import Data.ByteString as X (ByteString)
import Data.Foldable as X (for_)
import Data.Maybe as X
(catMaybes, fromMaybe, isJust, isNothing, listToMaybe, mapMaybe)
( catMaybes,
fromMaybe,
isJust,
isNothing,
listToMaybe,
mapMaybe,
)
import Data.Text as X (Text, pack, unpack)
import Data.Traversable as X (for)
import GHC.Generics as X (Generic)
import Lens.Micro as X (Lens', lens)
import Lens.Micro.Mtl as X (view)
import Text.Read as X (readMaybe)
import UnliftIO.Exception as X (Exception(..), catch, throwIO)
import UnliftIO.Exception as X (Exception (..), catch, throwIO)
import Prelude as X
14 changes: 7 additions & 7 deletions library/Asana/Api/Project.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,18 @@
module Asana.Api.Project
( Project(..)
) where

import Asana.Api.Prelude
( Project (..),
)
where

import Asana.Api.Gid (Gid)
import Asana.Api.Prelude
import Data.Aeson (FromJSON, genericParseJSON, parseJSON)
import Data.Aeson.Casing (aesonPrefix, snakeCase)
import Data.Time (UTCTime)

data Project = Project
{ pGid :: Gid
, pName :: Text
, pCreatedAt :: UTCTime
{ pGid :: Gid,
pName :: Text,
pCreatedAt :: UTCTime
}
deriving stock (Generic, Show)

Expand Down
Loading

0 comments on commit fbdcd05

Please sign in to comment.