[Haskell-cafe] Is there a way to make this code compose generic ?

PICCA Frederic-Emmanuel frederic-emmanuel.picca at synchrotron-soleil.fr
Fri Apr 25 12:00:40 UTC 2025


Hello,

I played with the inspection library, 

- where I tryed to find typeclass dictionnay (no one :)

- but it can find '[] contructor. -> I need some help to understand the error message and if this is an issue ...sorry

- No generic code found , it is nice but surprising for me...

Cheers

Fred




./test/BinocularsSpec.hs:225:25: pro does not contain dictionary values passed.
./test/BinocularsSpec.hs:226:25: pro `hasNoType` GHC.Types.List failed:
pro :: LoggingT IO ()
[LclIdX,
 Arity=2,
 Str=<LC(S,L)><L>,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}]
pro
  = pro_sjFg
    `cast` (<Loc -> LogSource -> LogLevel -> LogStr -> IO ()>_R
            %<'Many>_N ->_R Sym (N:IO[0] <()>_R)
            ; Sym (N:LoggingT[0] <IO>_R <()>_N)
            :: Coercible
                 ((Loc -> LogSource -> LogLevel -> LogStr -> IO ())
                  -> State# RealWorld -> (# State# RealWorld, () #))
                 (LoggingT IO ()))

a1 :: Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
a1 = src<test/BinocularsSpec.hs:219:76-78> I# 120#

b :: Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
b = src<test/BinocularsSpec.hs:219:109-111> I# 453#

a1 :: Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
a1 = src<test/BinocularsSpec.hs:69:87-89> I# 123#

pro_skPp :: Addr#
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 20 0}]
pro_skPp = src<test/BinocularsSpec.hs:41:1-105> "toto"#

pro_sjFa :: [Char]
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=False, ConLike=True, WorkFree=False, Expandable=True,
         Guidance=IF_ARGS [] 20 0}]
pro_sjFa
  = src<test/BinocularsSpec.hs:41:1-105> unpackCString# pro_skPp

pro_sjFb :: Maybe FilePath
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_sjFb
  = src<test/BinocularsSpec.hs:41:1-105> Just @FilePath pro_sjFa

pro_sjIE :: Interval Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_sjIE
  = src<test/BinocularsSpec.hs:41:1-105>
    I @Int
      (src<test/BinocularsSpec.hs:41:71-73> a1)
      (src<test/BinocularsSpec.hs:41:71-73> a1)

pro_skPq :: Interval Int
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_skPq
  = src<test/BinocularsSpec.hs:41:1-105>
    I @Int
      (src<test/BinocularsSpec.hs:41:92-94> a1)
      (src<test/BinocularsSpec.hs:41:98-100> b)

pro_sjFd :: [InputRange]
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_sjFd
  = src<test/BinocularsSpec.hs:41:1-105>
    : @InputRange
      (pro_skPq
       `cast` (Sym (N:InputRange[0])
               :: Coercible (Interval Int) InputRange))
      ([] @InputRange)

pro_sjFe :: NonEmpty InputRange
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_sjFe
  = src<test/BinocularsSpec.hs:41:1-105>
    :|
      @InputRange
      (pro_sjIE
       `cast` (Sym (N:InputRange[0])
               :: Coercible (Interval Int) InputRange))
      pro_sjFd

pro_sjFf :: Maybe ConfigRange
[LclId,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 10 10}]
pro_sjFf
  = src<test/BinocularsSpec.hs:41:1-105>
    Just
      @ConfigRange
      (pro_sjFe
       `cast` (Sym (N:ConfigRange[0])
               :: Coercible (NonEmpty InputRange) ConfigRange))

pro_sjFg [Dmd=LC(S,C(1,L))]
  :: (Loc -> LogSource -> LogLevel -> LogStr -> IO ())
     -> State# RealWorld -> (# State# RealWorld, () #)
[LclId,
 Arity=2,
 Str=<LC(S,L)><L>,
 Unf=Unf{Src=<vanilla>, TopLvl=True,
         Value=True, ConLike=True, WorkFree=True, Expandable=True,
         Guidance=IF_ARGS [] 30 60}]
pro_sjFg
  = src<test/BinocularsSpec.hs:41:1-105> process1 pro_sjFb pro_sjFf

./test/BinocularsSpec.hs:227:25: pro mentions none of GHC.Generics.V1, GHC.Generics.U1, GHC.Generics.M1, GHC.Generics.K1, GHC.Generics.:+:, GHC.Generics.:*:, GHC.Generics.:.:, GHC.Generics.Rec1, GHC.Generics.Par1 passed.
    display inspection information of binoculars-ng [✘]


More information about the Haskell-Cafe mailing list