[Haskell-beginners] "Phantom" function?

Baa aquagnu at gmail.com
Fri Sep 15 10:05:52 UTC 2017


unfortunately call of new version:

  ..
  (isRight "data/a.json" :: VerifyJson RESTResp) `shouldReturn` True
  ..

leads to new errors:

       • Ambiguous type variable ‘a0’ arising from a use of ‘isRight’
          prevents the constraint ‘(aeson-1.0.2.1:Data.Aeson.Types.FromJSON.FromJSON
                                      a0)’ from being solved.
          Probable fix: use a type annotation to specify what ‘a0’ should be.
          These potential instances exist:
       .....
        • In the first argument of ‘shouldReturn’, namely
            ‘(isRight "data/a.json" :: VerifyJson RESTResp)’
          In a stmt of a 'do' block:
            (isRight "data/a.json" :: VerifyJson RESTResp) `shouldReturn` True
          In the second argument of ‘($)’, namely
            ‘do { (isRight "data/a.json" :: VerifyJson RESTResp)
                  `shouldReturn` True }’

I will be grateful for any help.

===
Best regards, Paul


> Seems that this works:
> 
>   {-# LANGUAGE ExistentialQuantification #-}
>   ...
> 
>   type VerifyJson a = IO Bool
> 
>   isRight :: forall a. FromJSON a => FilePath -> VerifyJson a
>   isRight testbed = do
>     js <- readFile testbed
>     return $ MB.isJust (decode js::Maybe a)
> 
> but what is the difference?!?
> 
> 
> > Hello, List. I'm trying to write function like this:
> > 
> >   type VerifyJson a = IO Bool
> > 
> >   isRight :: FromJSON a => FilePath -> VerifyJson a
> >   isRight testbed = do
> >     js <- readFile testbed
> >     return $ isJust (decode js) <<<<< ERROR IS HERE ! 
> > 
> > So I get error:
> > 
> >     60  23 error           error:
> >      • Could not deduce (FromJSON a0) arising from a use of ‘decode’
> >        from the context: FromJSON a
> >          bound by the type signature for:
> >                     isRight :: FromJSON a => FilePath -> VerifyJson
> > a
> > at /home/XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX/.stack-work/intero/intero7476qP4.hs:57:1-46
> > The type variable ‘a0’ is ambiguous These potential instances exist:
> >          instance FromJSON DotNetTime
> >            -- Defined in ‘aeson-1.0.2.1:Data.Aeson.Types.FromJSON’
> >          instance FromJSON Value
> >            -- Defined in ‘aeson-1.0.2.1:Data.Aeson.Types.FromJSON’
> >          instance (FromJSON a, FromJSON b) => FromJSON (Either a b)
> >            -- Defined in ‘aeson-1.0.2.1:Data.Aeson.Types.FromJSON’
> >          ...plus 25 others
> >          ...plus 52 instances involving out-of-scope types
> >          (use -fprint-potential-instances to see them all)
> >      • In the first argument of ‘MB.isJust’, namely ‘(decode js)’
> >        In the second argument of ‘($)’, namely ‘MB.isJust (decode
> > js)’ In a stmt of a 'do' block: return $ MB.isJust (decode js)
> > (intero)
> > 
> > Is it possible to write such (phantom?;)) function? Sure, I can make
> > workaround like:
> > 
> >     class FromJSON a => VerifyJson a where
> >       isRight :: FilePath -> IO Bool
> >       isRight testbed = do
> >         js <- readFile testbed
> >         return $ MB.isJust (decode js::Maybe a)
> > 
> > but in this case I must declare instances for all verificating types
> > (right?), like:
> > 
> >     instance VerifyJson MyType
> > 
> > But idea was to minimize `isRight` users code...
> > 
> > ===
> > Best regards, Paul
> >   
> 



More information about the Beginners mailing list