-- | This module contains everything you need to -- perform PokitDok Platform API calls. module PokitDok.Client where import PokitDok.Requests import PokitDok.OAuth2 import PokitDok.Paths -- * Credentials -- | Generates a new key with the given id and secret. keyWithIdSecret :: String -> String -> OAuth2 keyWithIdSecret id secret = OAuth2 { oauthClientId = id , oauthClientSecret = secret , oauthAccessTokenEndpoint = apiSite ++ apiTokenPath , oauthOAuthorizeEndpoint = Just $ apiSite ++ apiEndpointAuthorizations , oauthCallback = Nothing , oauthAccessToken = Nothing } -- | Modifies the given key's callback url with the given @Maybe String@. keyModCallback :: OAuth2 -> Maybe String -> OAuth2 keyModCallback oauth n@Nothing = oauth { oauthCallback = n } keyModCallback oauth j = oauth { oauthCallback = j } -- | A url where a user can obtain an access token. -- Throws an error unless @keyModCallback@ is used on the credential first. authorizationUrl :: OAuth2 -> String authorizationUrl (OAuth2 id sec _ (Just authEP) (Just cb) _) = authEP `appendParams` authorizationUrlParams where authorizationUrlParams = [ ("client_id" , id) , ("response_type", "code") , ("redirect_uri" , cb) , ("scope" , "user_schedule") ] authorizationUrl _ = error "Cannot generate authoirzation url without a callback url." -- | Checks if the given @OAuth2@'s @AccessToken@ is expired. isExpired :: OAuth2 -> IO Bool isExpired (OAuth2 _ _ _ _ _ (Just at)) = isExpired' at isExpired _ = return True -- | Takes an @OAuth2@ and returns an @IO@ @OAuth2@ with a valid @AccessToken@. refresh :: OAuth2 -> IO OAuth2 refresh auth = isExpired auth >>= refreshExpired auth -- | Authenticate's an @OAuth2@ given an authorization code. authenticateCode :: OAuth2 -> String -> IO OAuth2 authenticateCode = activateKeyWithAuthCode -- * API Calls -- | Call the activities endpoint for a specific activityId. -- See docs here: activitiesWithId :: OAuth2 -- ^ Credentials with a valid @'AccessToken'@ -> String -- ^ Activity identifier. -> IO String -- ^ JSON formatted data. activitiesWithId auth id = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointActivities ++ id -- | Call the activities endpoint to get a listing of current activities, -- a query string parameter @parent_id@ may also be used with this API to get information about -- sub-activities that were initiated from a batch file upload. -- See docs here: activities :: OAuth2 -> Parameters -- ^ _id, name, callback_url, file_url, history, state, transition_path... -> IO String activities auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointActivities -- | Return a list of cash prices for a given procedure -- code in a given region (by ZIP Code). -- See docs here: pricesCash :: OAuth2 -> Parameters -- ^ cpt_code, zip_code (wthin with to search) -> IO String pricesCash auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointPriceCash -- | Return a list of insurance prices for a given procedure code -- in a given region (by ZIP Code). -- See docs here: pricesInsurance :: OAuth2 -> Parameters -- ^ cpt_code, zip_code -> IO String pricesInsurance auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointPriceInsurance -- | Create a new claim, via the filing of an EDI 837 Professional Claims, to the designated Payer. -- See docs here: claims :: OAuth2 -> String -- ^ Dictionary representing JSON post data. -> IO String claims auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointClaims -- | Ascertain the status of the specified claim, via the filing of an EDI 276 Claims Status. -- See docs here: claimsStatus :: OAuth2 -> String -> IO String claimsStatus auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointClaimsStatus -- | Determine eligibility via an EDI 270 Request For Eligibility. -- See docs here: eligibility :: OAuth2 -> String -- Dictionary representing an EDI 270 Request For Eligibility, JSON. -> IO String eligibility auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointEligibility -- | File an EDI 834 benefit enrollment. -- See docs here: enrollment :: OAuth2 -> String -- ^ Post data, JSON. -> IO String enrollment auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointEnrollment -- | Retrieve providers data matching specified query parameters. -- See docs here: providers :: OAuth2 -> Parameters -- ^ organization_name, first_name, last_name, specialty, city, state, radius... -> IO String providers auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointProviders -- | Retrieve the data for a specified provider. -- See docs here: providersWithNpi :: OAuth2 -> String -- Provider NPI identifier, JSON. -> IO String providersWithNpi auth npi = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointProviders++npi -- | Retrieve data on plans based on the parameters given. -- See docs here: plans :: OAuth2 -> Parameters -- ^ trading_partner_id, country, state, plan_id, plan_type, plan_name... -> IO String plans auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointPlans -- | Use the /payers/ API to determine available @payer_id@ values for use with other endpoints. -- This endpoint will be deprecated in v5. Use /Trading Partners/ instead. -- See docs here: payers :: OAuth2 -> IO String payers auth = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointPayers -- | Retrieve a list of trading partners or submit an id to get info for a -- specific trading partner. Empty string is a valid parameter. -- See docs here: tradingPartners :: OAuth2 -> String -- Trading Partner Identifier, can be empty. -> IO String tradingPartners auth id = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path++apiEndpointTradingPartners++id -- | Submit an X12 formatted EDI file for batch processing. -- If the callback url is not nothing in the @OAuth2@, it will be included. files :: OAuth2 -> String -- ^ Trading_partner_id. -> String -- ^ Full filesytem path of file to be submitted. -> IO String files auth trPartId filePath = assertValid auth >> do let postData = ("trading_partner_id",trPartId) : case oauthCallback auth of (Just cb) -> [("callback_url",cb)] otherwise -> [] pokitdokMultipartRequest auth url postData filePath >>= getJSONIO where url = path ++ apiEndpointFiles -- | Request approval for a referral to another health care provider. -- See docs here: referrals :: OAuth2 -> String -> IO String referrals auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointReferrals -- | Submit an authorization request. -- See docs here: authorizations :: OAuth2 -> String -- Dictionary representing JSON post data. -> IO String authorizations auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointAuthorizations -- | Get a list of supported scheduling systems and their UUIDs & descriptions. schedulers :: OAuth2 -> String -- ^ Empty string valid, retrieve the data for a specified scheduling system. -> IO String schedulers auth uuid = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointSchedulers ++ uuid -- | Get a list of appointment types, their UUIDs, and descriptions. appointmentTypes :: OAuth2 -> String -- ^ Empty string valid, retrieve the data for a specified appointment type. -> IO String appointmentTypes auth uuid = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointAppointmentTypes ++ uuid -- | Create an available appointment slot in the PokitDok scheduler system. createSlot :: OAuth2 -> String -- ^ Available appointment slot details, JSON. -> IO String createSlot auth json = assertValid auth >> pokitdokPostRequest auth url json >>= getJSONIO where url = path ++ apiEndpointSlots -- | Query for an open appointment slot or a booked appointment given a -- specific @pd_appointment_uuid@, the PokitDok unique appointment identifier. -- See appointmentsWithId :: OAuth2 -> String -- ^ The PokitDok unique appointment identifier. -> IO String appointmentsWithId auth uuid = assertValid auth >> pokitdokGetRequest auth url [] >>= getJSONIO where url = path ++ apiEndpointAppointments ++ uuid -- | Query for open appointment slots (using @pd_provider_uuid@ and @location@) -- or booked appointments (using @patient_uuid@2) given query parameters. -- See appointments :: OAuth2 -> Parameters -> IO String appointments auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointAppointments -- | Book appointment for an open slot. Post data contains patient -- attributes and description. -- See bookAppointment :: OAuth2 -> String -- ^ The PokitDok unique appointment identifier. -> String -- ^ Put data, JSON. -> IO String bookAppointment auth uuid json = assertValid auth >> pokitdokPutRequest auth url json >>= getJSONIO where url = path ++ apiEndpointAppointments ++ uuid -- | Update appointment description. -- See updateAppointment :: OAuth2 -> String -> String -> IO String updateAppointment auth uuid json = assertValid auth >> pokitdokPutRequest auth url json >>= getJSONIO where url = path ++ apiEndpointAppointments ++ uuid -- | Cancel appointment given its @pd_appointment_uuid@. -- See cancelAppointment :: OAuth2 -> String -> IO String cancelAppointment auth uuid = assertValid auth >> pokitdokDeleteRequest auth url >>= getJSONIO where url = path ++ apiEndpointAppointments ++ uuid {--- | Get a list of medical procedure information meeting certain -- search criteria. -- See docs here: https://platform.pokitdok.com/documentation/v4#/#mpc medicalProcedureCode :: OAuth2 -> Parameters -> IO String medicalProcedureCode auth params = assertValid auth >> pokitdokGetRequest auth url params >>= getJSONIO where url = path ++ apiEndpointMPC -- | Retrieve the data for a specific procedure code. medicalProcedureCodeWithMPC :: OAuth2 -> String -> IO String medicalProcedureCodeWithMPC auth mpc = assertValid auth >> pokitdokGetRequest auth url >>= getJSONIO where url = path ++ apiEndpointMPC ++ mpc-}