Skip to content
  • $ _build/stage1/bin/ghc -ddump-simpl -O2 -fforce-recomp -ddump-str-signatures -ddump-cpr-signatures -ddump-cpranal -ddump-prep -dno-typeable-binds SimpleTest.hs
    [1 of 1] Compiling Test             ( SimpleTest.hs, SimpleTest.o )
    
    ==================== Strictness signatures ====================
    Test.test: <L,U><L,U>
    
    
    
    ==================== Cpr signatures ====================
    Test.test:
    
    
    
    ==================== Constructed Product Result analysis ====================
    Result size of Constructed Product Result analysis
      = {terms: 39, types: 64, coercions: 7, joins: 0/0}
    
    -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
    lvl_s1JP :: Addr#
    [LclId,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
    lvl_s1JP = "positive"#
    
    -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
    lvl_s1JG :: [Char]
    [LclId,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=True,
             WorkFree=False, Expandable=True, Guidance=IF_ARGS [] 20 0}]
    lvl_s1JG = GHC.CString.unpackCString# lvl_s1JP
    
    -- RHS size: {terms: 5, types: 9, coercions: 0, joins: 0/0}
    lvl_s1JB :: State# RealWorld -> (# State# RealWorld, Int #)
    [LclId,
     Arity=1,
     Str=<L,U>,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True,
             Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}]
    lvl_s1JB
      = \ (s_a1IB [OS=OneShot] :: State# RealWorld) ->
          (# s_a1IB, GHC.Types.I# 42# #)
    
    -- RHS size: {terms: 25, types: 28, coercions: 2, joins: 0/0}
    test_s1Jw
      :: ByteArray# -> State# RealWorld -> (# State# RealWorld, () #)
    [LclId,
     Arity=2,
     Str=<L,U><L,U>,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True, Guidance=IF_ARGS [0 0] 111 30}]
    test_s1Jw
      = \ (ba_ay7 :: ByteArray#) (s_a1Is :: State# RealWorld) ->
          case with#
                 @'UnliftedRep @ByteArray# @'LiftedRep @Int ba_ay7 lvl_s1JB s_a1Is
          of
          { (# ipv_a1Iu, ipv1_a1Iv [Dmd=<S,1*U(U)>] #) ->
          case ipv1_a1Iv of { I# x_a1II ->
          case ># x_a1II 0# of {
            __DEFAULT -> (# ipv_a1Iu, GHC.Tuple.() #);
            1# ->
              ((GHC.IO.Handle.Text.hPutStr'
                  GHC.IO.Handle.FD.stdout lvl_s1JG GHC.Types.True)
               `cast` (GHC.Types.N:IO[0] <()>_R
                       :: IO () ~R# (State# RealWorld -> (# State# RealWorld, () #))))
                ipv_a1Iu
          }
          }
          }
    
    -- RHS size: {terms: 1, types: 0, coercions: 5, joins: 0/0}
    test :: ByteArray# -> IO ()
    [LclIdX,
     Arity=2,
     Str=<L,U><L,U>,
     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)}]
    test
      = test_s1Jw
        `cast` (<ByteArray#>_R ->_R Sym (GHC.Types.N:IO[0] <()>_R)
                :: (ByteArray# -> State# RealWorld -> (# State# RealWorld, () #))
                   ~R# (ByteArray# -> IO ()))
    
    
    
    
    ==================== Strictness signatures ====================
    Test.test: <L,U><L,U>
    
    
    
    ==================== Tidy Core ====================
    Result size of Tidy Core
      = {terms: 41, types: 65, coercions: 7, joins: 0/0}
    
    -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
    Test.test3 :: Addr#
    [GblId,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
    Test.test3 = "positive"#
    
    -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
    Test.test2 :: [Char]
    [GblId,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=True,
             WorkFree=False, Expandable=True, Guidance=IF_ARGS [] 20 0}]
    Test.test2 = GHC.CString.unpackCString# Test.test3
    
    -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
    lvl_r1I6 :: Int
    [GblId, Unf=OtherCon []]
    lvl_r1I6 = GHC.Types.I# 42#
    
    -- RHS size: {terms: 4, types: 9, coercions: 0, joins: 0/0}
    Test.test4 :: State# RealWorld -> (# State# RealWorld, Int #)
    [GblId,
     Arity=1,
     Str=<L,U>,
     Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True,
             Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)
             Tmpl= \ (s_a1IB [Occ=Once, OS=OneShot] :: State# RealWorld) ->
                     (# s_a1IB, GHC.Types.I# 42# #)}]
    Test.test4
      = \ (s_a1IB [OS=OneShot] :: State# RealWorld) ->
          (# s_a1IB, lvl_r1I6 #)
    
    -- RHS size: {terms: 25, types: 28, coercions: 2, joins: 0/0}
    Test.test1
      :: ByteArray# -> State# RealWorld -> (# State# RealWorld, () #)
    [GblId,
     Arity=2,
     Str=<L,U><L,U>,
     Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True, Guidance=IF_ARGS [0 0] 111 30}]
    Test.test1
      = \ (ba_ay7 :: ByteArray#) (s_a1Is :: State# RealWorld) ->
          case with#
                 @'UnliftedRep @ByteArray# @'LiftedRep @Int ba_ay7 Test.test4 s_a1Is
          of
          { (# ipv_a1Iu, ipv1_a1Iv #) ->
          case ipv1_a1Iv of { I# x_a1II ->
          case ># x_a1II 0# of {
            __DEFAULT -> (# ipv_a1Iu, GHC.Tuple.() #);
            1# ->
              ((GHC.IO.Handle.Text.hPutStr'
                  GHC.IO.Handle.FD.stdout Test.test2 GHC.Types.True)
               `cast` (GHC.Types.N:IO[0] <()>_R
                       :: IO () ~R# (State# RealWorld -> (# State# RealWorld, () #))))
                ipv_a1Iu
          }
          }
          }
    
    -- RHS size: {terms: 1, types: 0, coercions: 5, joins: 0/0}
    test :: ByteArray# -> IO ()
    [GblId,
     Arity=2,
     Str=<L,U><L,U>,
     Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
             WorkFree=True, Expandable=True,
             Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)
             Tmpl= Test.test1
                   `cast` (<ByteArray#>_R ->_R Sym (GHC.Types.N:IO[0] <()>_R)
                           :: (ByteArray# -> State# RealWorld -> (# State# RealWorld, () #))
                              ~R# (ByteArray# -> IO ()))}]
    test
      = Test.test1
        `cast` (<ByteArray#>_R ->_R Sym (GHC.Types.N:IO[0] <()>_R)
                :: (ByteArray# -> State# RealWorld -> (# State# RealWorld, () #))
                   ~R# (ByteArray# -> IO ()))
    
    
    
    
    ==================== CorePrep ====================
    Result size of CorePrep
      = {terms: 53, types: 86, coercions: 7, joins: 0/0}
    
    -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
    Test.test3 :: GHC.Prim.Addr#
    [GblId, Unf=OtherCon []]
    Test.test3 = "positive"#
    
    -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
    Test.test2 :: [GHC.Types.Char]
    [GblId]
    Test.test2 = GHC.CString.unpackCString# Test.test3
    
    -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
    lvl_r1I6 :: GHC.Types.Int
    [GblId, Unf=OtherCon []]
    lvl_r1I6 = GHC.Types.I# 42#
    
    -- RHS size: {terms: 4, types: 9, coercions: 0, joins: 0/0}
    Test.test4
      :: GHC.Prim.State# GHC.Prim.RealWorld
         -> (# GHC.Prim.State# GHC.Prim.RealWorld, GHC.Types.Int #)
    [GblId, Arity=1, Str=<L,U>, Unf=OtherCon []]
    Test.test4
      = \ (s_s1L0 [Occ=Once, OS=OneShot]
             :: GHC.Prim.State# GHC.Prim.RealWorld) ->
          (# s_s1L0, lvl_r1I6 #)
    
    -- RHS size: {terms: 33, types: 46, coercions: 2, joins: 0/0}
    Test.test1
      :: GHC.Prim.ByteArray#
         -> GHC.Prim.State# GHC.Prim.RealWorld
         -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #)
    [GblId, Arity=2, Str=<L,U><L,U>, Unf=OtherCon []]
    Test.test1
      = \ (ba_s1L1 [Occ=Once] :: GHC.Prim.ByteArray#)
          (s_s1L2 [Occ=Once] :: GHC.Prim.State# GHC.Prim.RealWorld) ->
          case case Test.test4 s_s1L2 of
               { (# sat_s1L8 [Occ=Once], sat_s1L9 [Occ=Once] #) ->
               case GHC.Prim.touch#
                      @'GHC.Types.UnliftedRep @GHC.Prim.ByteArray# ba_s1L1 sat_s1L8
               of sat_s1La [Occ=Once]
               { __DEFAULT ->
               (# sat_s1La, sat_s1L9 #)
               }
               }
          of
          { (# ipv_s1Lc [Occ=Once*], ipv1_s1Ld [Occ=Once!] #) ->
          case ipv1_s1Ld of { GHC.Types.I# x_s1Lf [Occ=Once] ->
          case GHC.Prim.># x_s1Lf 0# of {
            __DEFAULT -> (# ipv_s1Lc, GHC.Tuple.() #);
            1# ->
              ((GHC.IO.Handle.Text.hPutStr'
                  GHC.IO.Handle.FD.stdout Test.test2 GHC.Types.True)
               `cast` (GHC.Types.N:IO[0] <()>_R
                       :: GHC.Types.IO ()
                          ~R# (GHC.Prim.State# GHC.Prim.RealWorld
                               -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #))))
                ipv_s1Lc
          }
          }
          }
    
    -- RHS size: {terms: 5, types: 3, coercions: 5, joins: 0/0}
    Test.test :: GHC.Prim.ByteArray# -> GHC.Types.IO ()
    [GblId, Arity=2, Str=<L,U><L,U>, Unf=OtherCon []]
    Test.test
      = (\ (eta_B2 [Occ=Once] :: GHC.Prim.ByteArray#)
           (eta_B1 [Occ=Once] :: GHC.Prim.State# GHC.Prim.RealWorld) ->
           Test.test1 eta_B2 eta_B1)
        `cast` (<GHC.Prim.ByteArray#>_R ->_R Sym (GHC.Types.N:IO[0] <()>_R)
                :: (GHC.Prim.ByteArray#
                    -> GHC.Prim.State# GHC.Prim.RealWorld
                    -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #))
                   ~R# (GHC.Prim.ByteArray# -> GHC.Types.IO ()))
    
    
    
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