Skip to content

Instantly share code, notes, and snippets.

@Goheeca
Last active November 29, 2021 19:04
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save Goheeca/096d7ebc0a5551d147df8b68bf4fe2d2 to your computer and use it in GitHub Desktop.
Save Goheeca/096d7ebc0a5551d147df8b68bf4fe2d2 to your computer and use it in GitHub Desktop.
refined library issue
#!/usr/bin/env stack
-- stack --resolver lts-18.5 script --package template-haskell --package refined
{-# LANGUAGE TemplateHaskell, TypeApplications #-}
import Refined
import Data.Either
import RefinedTestDefinitions
refinedTypeAppliedTest :: RefinedTest Int
refinedTypeAppliedTest = $$(refineTH $ UnrefinedTest @Int 0)
refinedTest :: RefinedTest Int
refinedTest = $$(refineTH $ UnrefinedTest 0)
wrappedRefinedTypeAppliedTest :: WrappedRefinedTest Int
wrappedRefinedTypeAppliedTest = WrappedRefinedTest $ fromRight undefined $ refine $ UnrefinedTest @Int 0
wrappedRefinedTest :: WrappedRefinedTest Int
wrappedRefinedTest = WrappedRefinedTest $ fromRight undefined $ refine $ UnrefinedTest 0
wrappedRefinedTypeAppliedTHTest :: WrappedRefinedTest Int
wrappedRefinedTypeAppliedTHTest = WrappedRefinedTest $$(refineTH $ UnrefinedTest @Int 0)
{- The following fails because:
• Ambiguous type variable ‘a0’ arising from a use of ‘refineTH’
prevents the constraint ‘(Language.Haskell.TH.Syntax.Lift
a0)’ from being solved.
• Ambiguous type variable ‘a0’ arising from the literal ‘0’
prevents the constraint ‘(Num a0)’ from being solved.
-}
wrappedRefinedTHTest :: WrappedRefinedTest Int
wrappedRefinedTHTest = WrappedRefinedTest $$(refineTH $ UnrefinedTest 0)
main = pure ()
{-# LANGUAGE DeriveLift, MultiParamTypeClasses #-}
module RefinedTestDefinitions (
UnrefinedTest(..),
RefinedTest,
WrappedRefinedTest(..),
) where
import Refined
import Language.Haskell.TH.Syntax
data UnrefinedTest a = UnrefinedTest a deriving Lift
data TestValidator
instance Predicate TestValidator (UnrefinedTest a) where
validate _ _ = Nothing
type RefinedTest a = Refined TestValidator (UnrefinedTest a)
newtype WrappedRefinedTest a = WrappedRefinedTest (RefinedTest a)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment