fix for os_status (diamond added)

Also, some 'fail' refactoring
parent c2114adb
......@@ -17,6 +17,7 @@ module OpenAlex.Types where
import Control.Monad.Fail (fail)
import Data.Aeson
import Data.Aeson.Types (prependFailure, typeMismatch)
import Data.Csv qualified as Csv
import Data.Scientific (floatingOrInteger)
import Data.Text qualified as T
......@@ -47,26 +48,27 @@ instance FromJSON ExternalID where
parseJSON (String v) = pure $ ExtIDUrl v
parseJSON (Number n) =
case (floatingOrInteger n :: Either Double Integer) of
Left _ -> fail "Floating number not supported as external id"
Left _ -> fail $ "Floating number not supported as external id: " <> Protolude.show n
Right i -> pure $ ExtIDInt $ fromIntegral i
parseJSON a@(Array _a) =do
ids <- parseJSONList a
pure $ ExtIDUrls ids
parseJSON _ = fail "Don't know how to handle this external id"
parseJSON v = fail $ "Don't know how to handle this external id: " <> Protolude.show v
type ISSN = Text
type ISSNL = Text
type Language = Text -- TODO: https://doc.wikimedia.org/mediawiki-core/master/php/Names_8php_source.html
type Level = Int
-- |https://docs.openalex.org/api-entities/works/work-object#oa_status
data OAStatus = OAGold | OAGreen | OAHybrid | OABronze | OAClosed
data OAStatus = OADiamond | OAGold | OAGreen | OAHybrid | OABronze | OAClosed
deriving (Generic, Show)
instance FromJSON OAStatus where
parseJSON (String "diamond") = pure OADiamond
parseJSON (String "gold") = pure OAGold
parseJSON (String "green") = pure OAGreen
parseJSON (String "hybrid") = pure OAHybrid
parseJSON (String "bronze") = pure OABronze
parseJSON (String "closed") = pure OAClosed
parseJSON _ = fail "Don't know how to parse this oa status"
parseJSON s = fail $ "Don't know how to parse this oa status: " <> Protolude.show s
type OpenAlexID = Text
type URL = Text
type Year = Int
......@@ -79,8 +81,8 @@ type Year = Int
-- instance FromJSON UpdatedDate
parseTimeE :: (MonadFail m, DTF.ParseTime t) => Text -> Text -> m t
parseTimeE fmt s = case (DTF.parseTimeM True DTF.defaultTimeLocale (T.unpack fmt) (T.unpack s)) of
Nothing -> fail $ "Cannot parse date with format " <> T.unpack fmt
parseTimeE fmt s = case DTF.parseTimeM True DTF.defaultTimeLocale (T.unpack fmt) (T.unpack s) of
Nothing -> fail $ "Cannot parse date '" <> T.unpack s <> "' with format " <> T.unpack fmt
Just p -> pure p
-- | Convert to ISO text format
......@@ -131,7 +133,7 @@ instance FromJSON ExternalDB where
parseJSON (String "umls_aui") = pure UMLS_Aui
parseJSON (String "wikidata") = pure Wikidata
parseJSON (String "wikipedia") = pure Wikipedia
parseJSON _ = fail "Don't know how to handle this external db"
parseJSON v = fail $ "Don't know how to handle this external db: " <> Protolude.show v
data Meta = Meta
{ count :: Count
......@@ -193,7 +195,7 @@ instance FromJSON Concept where
works_api_url <- v .: "works_api_url"
works_count <- v .: "works_count"
pure $ Concept { .. }
parseJSON _ = fail "Cannot parse Concept as a non-object"
parseJSON v = prependFailure "Cannot parse Concept as a non-object" (typeMismatch "Object" v)
-- | https://docs.openalex.org/api-entities/concepts/concept-object#the-dehydratedconcept-object
data DehydratedConcept = DehydratedConcept
......@@ -225,11 +227,13 @@ data SummaryStats = SummaryStats
, i10_index :: Int
} deriving (Generic, Show)
instance FromJSON SummaryStats where
parseJSON (Object v) =
SummaryStats <$> v .: "2yr_mean_citedness"
<*> v .: "h_index"
<*> v .: "i10_index"
parseJSON _ = fail "Don't know how to parse this as SummaryStats"
parseJSON (Object o) = do
two_year_mean_citedness <- o .: "2yr_mean_citedness"
h_index <- o .: "h_index"
i10_index <- o .: "i10_index"
return $ SummaryStats { .. }
parseJSON v = prependFailure "Don't know how to parse this as SummaryStats" (typeMismatch "Object" v)
-- | https://docs.openalex.org/api-entities/works/work-object
......@@ -392,14 +396,14 @@ data DehydratedInstitution = DehydratedInstitution
, type_ :: Maybe Text
} deriving (Generic, Show)
instance FromJSON DehydratedInstitution where
parseJSON (Object v) = do
id <- v .:? "id"
display_name <- v .: "display_name"
ror <- v .:? "ror"
country_code <- v .:? "country_code"
type_ <- v .:? "type"
parseJSON (Object o) = do
id <- o .:? "id"
display_name <- o .: "display_name"
ror <- o .:? "ror"
country_code <- o .:? "country_code"
type_ <- o .:? "type"
pure $ DehydratedInstitution { .. }
parseJSON _ = fail "Don't know how to parse a dehydrated institution from a non-object"
parseJSON v = prependFailure "Don't know how to parse a dehydrated institution from a non-object" (typeMismatch "Object" v)
data Grant = Grant
{ funder :: OpenAlexID
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment