Skip to content

Instantly share code, notes, and snippets.

@kana-sama
Last active February 21, 2021 11:45
Show Gist options
  • Save kana-sama/82e01dff7c01df24a6a15cc57adc1d62 to your computer and use it in GitHub Desktop.
Save kana-sama/82e01dff7c01df24a6a15cc57adc1d62 to your computer and use it in GitHub Desktop.
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module Main (main, values) where
import GHC.Generics
data X = A Int | B String | C Int
deriving (Show)
instance Generic X where
from x_a35Y =
M1
( case x_a35Y of
A g1_a35Z ->
L1
(M1 (M1 (K1 g1_a35Z)))
B g1_a360 ->
R1
( L1
(M1 (M1 (K1 g1_a360)))
)
C g1_a361 ->
R1
( R1
(M1 (M1 (K1 g1_a361)))
)
)
to (M1 x_a362) =
case x_a362 of
(L1 (M1 (M1 (K1 g1_a363)))) ->
A g1_a363
(R1 (L1 (M1 (M1 (K1 g1_a364))))) ->
B g1_a364
(R1 (R1 (M1 (M1 (K1 g1_a365))))) ->
C g1_a365
{-# INLINE [1] to #-}
{-# INLINE [1] from #-}
type
Rep X =
D1
('MetaData "X" "Main" "main" 'False)
( C1
( 'MetaCons
"A"
'PrefixI
'False
)
( S1
( 'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy
)
(Rec0 Int)
)
:+: ( C1
( 'MetaCons
"B"
'PrefixI
'False
)
( S1
( 'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy
)
(Rec0 String)
)
:+: C1
( 'MetaCons
"C"
'PrefixI
'False
)
( S1
( 'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy
)
( Rec0
Int
)
)
)
)
class GBuild val r where
gbuild :: val -> [r x]
instance GBuild val cs => GBuild val (D1 meta cs) where
gbuild x = M1 <$> gbuild x
{-# INLINE [1] gbuild #-}
instance (GBuild val l, GBuild val r) => GBuild val (l :+: r) where
gbuild x = (L1 <$> gbuild x) <> (R1 <$> gbuild x)
{-# INLINE [1] gbuild #-}
instance {-# OVERLAPS #-} GBuild val (C1 cmeta (S1 smeta (Rec0 val))) where
gbuild x = [M1 (M1 (K1 x))]
{-# INLINE [1] gbuild #-}
instance GBuild val (C1 cmeta sels) where
gbuild _ = []
{-# INLINE [1] gbuild #-}
build :: (Generic a, GBuild val (Rep a)) => val -> [a]
build val = to <$> gbuild val
{-# INLINE [1] build #-}
{-# NOINLINE [1] values #-}
values :: [X]
values = build (10 :: Int)
main = print values
==================== Tidy Core ====================
2021-02-21 11:44:13.598881 UTC
Result size of Tidy Core
= {terms: 465, types: 1,973, coercions: 766, joins: 0/2}
-- RHS size: {terms: 4, types: 9, coercions: 3, joins: 0/0}
gbuild [InlPrag=INLINE]
:: forall val (r :: * -> *) x. GBuild val r => val -> [r x]
[GblId[ClassOp],
Arity=1,
Caf=NoCafRefs,
Str=<S,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=True)
Tmpl= \ (@ val_aHA)
(@ (r_aHB :: * -> *))
(v_B1 [Occ=Once] :: GBuild val_aHA r_aHB) ->
v_B1
`cast` (Main.N:GBuild[0] <val_aHA>_N <r_aHB>_N
:: GBuild val_aHA r_aHB ~R# (forall x. val_aHA -> [r_aHB x]))}]
gbuild
= \ (@ val_aHA)
(@ (r_aHB :: * -> *))
(v_B1 :: GBuild val_aHA r_aHB) ->
v_B1
`cast` (Main.N:GBuild[0] <val_aHA>_N <r_aHB>_N
:: GBuild val_aHA r_aHB ~R# (forall x. val_aHA -> [r_aHB x]))
-- RHS size: {terms: 8, types: 33, coercions: 37, joins: 0/0}
Main.$fGBuildvalM10_$cgbuild [InlPrag=INLINE[1] (sat-args=1)]
:: forall val (cmeta :: Meta) (smeta :: Meta) x.
val -> [C1 cmeta (S1 smeta (Rec0 val)) x]
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<L,U>m2,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=False)
Tmpl= \ (@ val_a2yq)
(@ (cmeta_a2yr :: Meta))
(@ (smeta_a2ys :: Meta))
(@ x_a2yw)
(x1_a11L [Occ=Once] :: val_a2yq) ->
ghc-prim-0.6.1:GHC.Types.:
@ (C1 cmeta_a2yr (S1 smeta_a2ys (Rec0 val_a2yq)) x_a2yw)
(x1_a11L
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<val_a2yq>_R
<x_a2yw>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<smeta_a2ys>_P
<K1
R
val_a2yq>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<cmeta_a2yr>_P
<M1
S
smeta_a2ys
(K1
R
val_a2yq)>_R)) <x_a2yw>_N
:: val_a2yq
~R# M1 C cmeta_a2yr (M1 S smeta_a2ys (K1 R val_a2yq)) x_a2yw))
(ghc-prim-0.6.1:GHC.Types.[]
@ (C1 cmeta_a2yr (S1 smeta_a2ys (Rec0 val_a2yq)) x_a2yw))}]
Main.$fGBuildvalM10_$cgbuild
= \ (@ val_a2yq)
(@ (cmeta_a2yr :: Meta))
(@ (smeta_a2ys :: Meta))
(@ x_a2yw)
(x1_a11L :: val_a2yq) ->
ghc-prim-0.6.1:GHC.Types.:
@ (C1 cmeta_a2yr (S1 smeta_a2ys (Rec0 val_a2yq)) x_a2yw)
(x1_a11L
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N <R>_P <val_a2yq>_R <x_a2yw>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<smeta_a2ys>_P
<K1
R
val_a2yq>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<cmeta_a2yr>_P
<M1
S
smeta_a2ys
(K1
R
val_a2yq)>_R)) <x_a2yw>_N
:: val_a2yq
~R# M1 C cmeta_a2yr (M1 S smeta_a2ys (K1 R val_a2yq)) x_a2yw))
(ghc-prim-0.6.1:GHC.Types.[]
@ (C1 cmeta_a2yr (S1 smeta_a2ys (Rec0 val_a2yq)) x_a2yw))
-- RHS size: {terms: 6, types: 15, coercions: 0, joins: 0/0}
Main.$fGBuildvalM1_$cgbuild [InlPrag=INLINE[1] (sat-args=1)]
:: forall val (cmeta :: Meta) (sels :: * -> *) x.
val -> [C1 cmeta sels x]
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<L,A>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=True)
Tmpl= \ (@ val_a2yf)
(@ (cmeta_a2yg :: Meta))
(@ (sels_a2yh :: * -> *))
(@ x_a2yl)
_ [Occ=Dead] ->
ghc-prim-0.6.1:GHC.Types.[] @ (C1 cmeta_a2yg sels_a2yh x_a2yl)}]
Main.$fGBuildvalM1_$cgbuild
= \ (@ val_a2yf)
(@ (cmeta_a2yg :: Meta))
(@ (sels_a2yh :: * -> *))
(@ x_a2yl)
_ [Occ=Dead] ->
ghc-prim-0.6.1:GHC.Types.[] @ (C1 cmeta_a2yg sels_a2yh x_a2yl)
-- RHS size: {terms: 16, types: 218, coercions: 199, joins: 0/0}
Main.$fGenericX_$cto [InlPrag=INLINE[1] (sat-args=1)]
:: forall x. Rep X x -> X
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<S,1*U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=False)
Tmpl= \ (@ x_a2Bb) (ds_d2RG [Occ=Once] :: Rep X x_a2Bb) ->
case ds_d2RG
`cast` ((Sub (Main.D:R:RepX[0]) ; GHC.Generics.N:M1[0]
<*>_N
<D>_P
<'MetaData "X" "Main" "main" 'False>_P
<M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
:+: (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons
"C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)))>_R) <x_a2Bb>_N
:: Rep X x_a2Bb
~R# (:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
(M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
x_a2Bb)
of {
L1 ds1_d2Tj [Occ=Once] ->
Main.A
(ds1_d2Tj
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "A" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
x_a2Bb
~R# Int));
R1 ds1_d2Tm [Occ=Once!] ->
case ds1_d2Tm of {
L1 ds2_d2Tn [Occ=Once] ->
Main.B
(ds2_d2Tn
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "B" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
String>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<String>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
x_a2Bb
~R# String));
R1 ds2_d2Tq [Occ=Once] ->
Main.C
(ds2_d2Tq
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "C" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
x_a2Bb
~R# Int))
}
}}]
Main.$fGenericX_$cto
= \ (@ x_a2Bb) (ds_d2RG :: Rep X x_a2Bb) ->
case ds_d2RG
`cast` ((Sub (Main.D:R:RepX[0]) ; GHC.Generics.N:M1[0]
<*>_N
<D>_P
<'MetaData "X" "Main" "main" 'False>_P
<M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
:+: (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))>_R) <x_a2Bb>_N
:: Rep X x_a2Bb
~R# (:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
(M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
x_a2Bb)
of {
L1 ds1_d2Tj ->
Main.A
(ds1_d2Tj
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "A" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1 R Int>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
x_a2Bb
~R# Int));
R1 ds1_d2Tm ->
case ds1_d2Tm of {
L1 ds2_d2Tn ->
Main.B
(ds2_d2Tn
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "B" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
String>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<String>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
x_a2Bb
~R# String));
R1 ds2_d2Tq ->
Main.C
(ds2_d2Tq
`cast` ((GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons "C" 'PrefixI 'False>_P
<M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)>_R ; GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1 R Int>_R) <x_a2Bb>_N ; GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_a2Bb>_P
:: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
x_a2Bb
~R# Int))
}
}
-- RHS size: {terms: 15, types: 282, coercions: 132, joins: 0/0}
$cfrom_r3Op
:: forall x.
X
-> (:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
(M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
x
[GblId, Arity=1, Caf=NoCafRefs, Str=<S,1*U>, Unf=OtherCon []]
$cfrom_r3Op
= \ (@ x_a2zX) (x_a35Y_a122 :: X) ->
case x_a35Y_a122 of {
A g1_a35Z_a123 ->
GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ x_a2zX
(g1_a35Z_a123
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N <R>_P <Int>_R <x_a2zX>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"A"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <x_a2zX>_N
:: Int
~R# M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
x_a2zX));
B g1_a360_a124 ->
GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ x_a2zX
(GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ x_a2zX
(g1_a360_a124
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N <R>_P <String>_R <x_a2zX>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
String>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"B"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
String)>_R)) <x_a2zX>_N
:: String
~R# M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
x_a2zX)));
C g1_a361_a125 ->
GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ x_a2zX
(GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ x_a2zX
(g1_a361_a125
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N <R>_P <Int>_R <x_a2zX>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"C"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <x_a2zX>_N
:: Int
~R# M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
x_a2zX)))
}
-- RHS size: {terms: 1, types: 0, coercions: 82, joins: 0/0}
Main.$fGenericX_$cfrom [InlPrag=INLINE[1] (sat-args=1)]
:: forall x. X -> Rep X x
[GblId,
Arity=1,
Caf=NoCafRefs,
Str=<S,1*U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=False)
Tmpl= (\ (@ x_X2AD) (x_a35Y_X12J [Occ=Once!] :: X) ->
case x_a35Y_X12J of {
A g1_a35Z_a123 [Occ=Once] ->
GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
@ x_X2AD
(g1_a35Z_a123
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_X2AD>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"A"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <x_X2AD>_N
:: Int
~R# M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
x_X2AD));
B g1_a360_a124 [Occ=Once] ->
GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
@ x_X2AD
(GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
@ x_X2AD
(g1_a360_a124
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<String>_R
<x_X2AD>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
String>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"B"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
String)>_R)) <x_X2AD>_N
:: String
~R# M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
x_X2AD)));
C g1_a361_a125 [Occ=Once] ->
GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
@ x_X2AD
(GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
@ x_X2AD
(g1_a361_a125
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<x_X2AD>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"C"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <x_X2AD>_N
:: Int
~R# M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
x_X2AD)))
})
`cast` (forall (x :: <*>_N).
<X>_R
->_R (Sym (GHC.Generics.N:M1[0]
<*>_N
<D>_P
<'MetaData "X" "Main" "main" 'False>_P
<M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int))
:+: (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)))>_R) ; Sub (Sym (Main.D:R:RepX[0]))) <x>_N
:: (forall x.
X
-> (:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
(M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))
x)
~R# (forall x. X -> Rep X x))}]
Main.$fGenericX_$cfrom
= $cfrom_r3Op
`cast` (forall (x :: <*>_N).
<X>_R
->_R (Sym (GHC.Generics.N:M1[0]
<*>_N
<D>_P
<'MetaData "X" "Main" "main" 'False>_P
<M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
:+: (M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1 R Int)))>_R) ; Sub (Sym (Main.D:R:RepX[0]))) <x>_N
:: (forall x.
X
-> (:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
(M1
C
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R String))
:+: M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int)))
x)
~R# (forall x. X -> Rep X x))
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
Main.$fGenericX [InlPrag=NOUSERINLINE CONLIKE] :: Generic X
[GblId[DFunId],
Caf=NoCafRefs,
Str=m,
Unf=DFun: \ ->
GHC.Generics.C:Generic TYPE: X
Main.$fGenericX_$cfrom
Main.$fGenericX_$cto]
Main.$fGenericX
= GHC.Generics.C:Generic
@ X Main.$fGenericX_$cfrom Main.$fGenericX_$cto
-- RHS size: {terms: 8, types: 14, coercions: 3, joins: 0/0}
$cgbuild_r3Oq
:: forall val (cs :: * -> *) (meta :: Meta) x.
GBuild val cs =>
val -> [cs x]
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<C(S),1*C1(U)><L,U>,
Unf=OtherCon []]
$cgbuild_r3Oq
= \ (@ val_a2zu)
(@ (cs_a2zv :: * -> *))
(@ (meta_a2zw :: Meta))
($dGBuild_a2zx :: GBuild val_a2zu cs_a2zv)
(@ x_a2zB)
(eta_B1 :: val_a2zu) ->
($dGBuild_a2zx
`cast` (Main.N:GBuild[0] <val_a2zu>_N <cs_a2zv>_N
:: GBuild val_a2zu cs_a2zv
~R# (forall x. val_a2zu -> [cs_a2zv x])))
@ x_a2zB eta_B1
-- RHS size: {terms: 1, types: 0, coercions: 28, joins: 0/0}
Main.$fGBuildvalM11_$cgbuild [InlPrag=INLINE[1] (sat-args=1)]
:: forall val (cs :: * -> *) (meta :: Meta) x.
GBuild val cs =>
val -> [D1 meta cs x]
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<C(S),1*C1(U)><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=2,unsat_ok=False,boring_ok=True)
Tmpl= (\ (@ val_X2AQ)
(@ (cs_X2AS :: * -> *))
(@ (meta_X2AU :: Meta))
($dGBuild_X2AW [Occ=Once] :: GBuild val_X2AQ cs_X2AS)
(@ x_X2B1)
(x1_a121 [Occ=Once] :: val_X2AQ) ->
($dGBuild_X2AW
`cast` (Main.N:GBuild[0] <val_X2AQ>_N <cs_X2AS>_N
:: GBuild val_X2AQ cs_X2AS
~R# (forall x. val_X2AQ -> [cs_X2AS x])))
@ x_X2B1 x1_a121)
`cast` (forall (val :: <*>_N) (cs :: <*
-> *>_N) (meta :: <Meta>_N).
<GBuild val cs>_R
->_R forall (x :: <*>_N).
<val>_R
->_R ([Sym (GHC.Generics.N:M1[0]
<*>_N <D>_P <meta>_P <cs>_R) <x>_N])_R
:: (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [cs x])
~R# (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [M1 D meta cs x]))}]
Main.$fGBuildvalM11_$cgbuild
= $cgbuild_r3Oq
`cast` (forall (val :: <*>_N) (cs :: <*
-> *>_N) (meta :: <Meta>_N).
<GBuild val cs>_R
->_R forall (x :: <*>_N).
<val>_R
->_R ([Sym (GHC.Generics.N:M1[0]
<*>_N <D>_P <meta>_P <cs>_R) <x>_N])_R
:: (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [cs x])
~R# (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [M1 D meta cs x]))
-- RHS size: {terms: 27, types: 73, coercions: 6, joins: 0/2}
Main.$fGBuildval:+:_$cgbuild [InlPrag=INLINE[1] (sat-args=1)]
:: forall val (l :: * -> *) (r :: * -> *) x.
(GBuild val l, GBuild val r) =>
val -> [(:+:) l r x]
[GblId,
Arity=3,
Caf=NoCafRefs,
Str=<C(S),1*C1(U)><L,1*C1(U)><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=3,unsat_ok=False,boring_ok=False)
Tmpl= \ (@ val_a2yO)
(@ (l_a2yP :: * -> *))
(@ (r_a2yQ :: * -> *))
($dGBuild_a2yR [Occ=Once] :: GBuild val_a2yO l_a2yP)
($dGBuild1_a2yS [Occ=Once] :: GBuild val_a2yO r_a2yQ)
(@ x_a2yW)
(x1_a11P :: val_a2yO) ->
++
@ ((:+:) l_a2yP r_a2yQ x_a2yW)
(map
@ (l_a2yP x_a2yW)
@ ((:+:) l_a2yP r_a2yQ x_a2yW)
(GHC.Generics.L1 @ * @ l_a2yP @ r_a2yQ @ x_a2yW)
(($dGBuild_a2yR
`cast` (Main.N:GBuild[0] <val_a2yO>_N <l_a2yP>_N
:: GBuild val_a2yO l_a2yP ~R# (forall x. val_a2yO -> [l_a2yP x])))
@ x_a2yW x1_a11P))
(map
@ (r_a2yQ x_a2yW)
@ ((:+:) l_a2yP r_a2yQ x_a2yW)
(GHC.Generics.R1 @ * @ l_a2yP @ r_a2yQ @ x_a2yW)
(($dGBuild1_a2yS
`cast` (Main.N:GBuild[0] <val_a2yO>_N <r_a2yQ>_N
:: GBuild val_a2yO r_a2yQ ~R# (forall x. val_a2yO -> [r_a2yQ x])))
@ x_a2yW x1_a11P))}]
Main.$fGBuildval:+:_$cgbuild
= \ (@ val_a2yO)
(@ (l_a2yP :: * -> *))
(@ (r_a2yQ :: * -> *))
($dGBuild_a2yR :: GBuild val_a2yO l_a2yP)
($dGBuild1_a2yS :: GBuild val_a2yO r_a2yQ)
(@ x_a2yW)
(eta_X1w :: val_a2yO) ->
let {
z_a2YK :: [(:+:) l_a2yP r_a2yQ x_a2yW]
[LclId]
z_a2YK
= map
@ (r_a2yQ x_a2yW)
@ ((:+:) l_a2yP r_a2yQ x_a2yW)
(GHC.Generics.R1 @ * @ l_a2yP @ r_a2yQ @ x_a2yW)
(($dGBuild1_a2yS
`cast` (Main.N:GBuild[0] <val_a2yO>_N <r_a2yQ>_N
:: GBuild val_a2yO r_a2yQ ~R# (forall x. val_a2yO -> [r_a2yQ x])))
@ x_a2yW eta_X1w) } in
letrec {
go_a2YL [Occ=LoopBreaker]
:: [l_a2yP x_a2yW] -> [(:+:) l_a2yP r_a2yQ x_a2yW]
[LclId, Arity=1, Str=<S,1*U>, Unf=OtherCon []]
go_a2YL
= \ (ds_a2YM :: [l_a2yP x_a2yW]) ->
case ds_a2YM of {
[] -> z_a2YK;
: y_a2YP ys_a2YQ ->
ghc-prim-0.6.1:GHC.Types.:
@ ((:+:) l_a2yP r_a2yQ x_a2yW)
(GHC.Generics.L1 @ * @ l_a2yP @ r_a2yQ @ x_a2yW y_a2YP)
(go_a2YL ys_a2YQ)
}; } in
go_a2YL
(($dGBuild_a2yR
`cast` (Main.N:GBuild[0] <val_a2yO>_N <l_a2yP>_N
:: GBuild val_a2yO l_a2yP ~R# (forall x. val_a2yO -> [l_a2yP x])))
@ x_a2yW eta_X1w)
-- RHS size: {terms: 1, types: 0, coercions: 22, joins: 0/0}
Main.$fGBuildvalM11 [InlPrag=INLINE (sat-args=0)]
:: forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs =>
GBuild val (D1 meta cs)
[GblId[DFunId(nt)],
Arity=2,
Caf=NoCafRefs,
Str=<C(S),1*C1(U)><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=True)
Tmpl= Main.$fGBuildvalM11_$cgbuild
`cast` (forall (val :: <*>_N) (cs :: <*
-> *>_N) (meta :: <Meta>_N).
<GBuild val cs>_R
->_R Sym (Main.N:GBuild[0] <val>_N <D1 meta cs>_N)
:: (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [D1 meta cs x])
~R# (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> GBuild val (D1 meta cs)))}]
Main.$fGBuildvalM11
= Main.$fGBuildvalM11_$cgbuild
`cast` (forall (val :: <*>_N) (cs :: <*
-> *>_N) (meta :: <Meta>_N).
<GBuild val cs>_R
->_R Sym (Main.N:GBuild[0] <val>_N <D1 meta cs>_N)
:: (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> forall x. val -> [D1 meta cs x])
~R# (forall val (cs :: * -> *) (meta :: Meta).
GBuild val cs -> GBuild val (D1 meta cs)))
-- RHS size: {terms: 1, types: 0, coercions: 29, joins: 0/0}
Main.$fGBuildval:+: [InlPrag=INLINE (sat-args=0)]
:: forall val (l :: * -> *) (r :: * -> *).
(GBuild val l, GBuild val r) =>
GBuild val (l :+: r)
[GblId[DFunId(nt)],
Arity=3,
Caf=NoCafRefs,
Str=<C(S),1*C1(U)><L,1*C1(U)><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=2,unsat_ok=False,boring_ok=True)
Tmpl= Main.$fGBuildval:+:_$cgbuild
`cast` (forall (val :: <*>_N) (l :: <* -> *>_N) (r :: <* -> *>_N).
<GBuild val l>_R
->_R <GBuild val r>_R
->_R Sym (Main.N:GBuild[0] <val>_N <l :+: r>_N)
:: (forall val (l :: * -> *) (r :: * -> *).
GBuild val l -> GBuild val r -> forall x. val -> [(:+:) l r x])
~R# (forall val (l :: * -> *) (r :: * -> *).
GBuild val l -> GBuild val r -> GBuild val (l :+: r)))}]
Main.$fGBuildval:+:
= Main.$fGBuildval:+:_$cgbuild
`cast` (forall (val :: <*>_N) (l :: <* -> *>_N) (r :: <* -> *>_N).
<GBuild val l>_R
->_R <GBuild val r>_R
->_R Sym (Main.N:GBuild[0] <val>_N <l :+: r>_N)
:: (forall val (l :: * -> *) (r :: * -> *).
GBuild val l -> GBuild val r -> forall x. val -> [(:+:) l r x])
~R# (forall val (l :: * -> *) (r :: * -> *).
GBuild val l -> GBuild val r -> GBuild val (l :+: r)))
-- RHS size: {terms: 1, types: 0, coercions: 22, joins: 0/0}
Main.$fGBuildvalM10 [InlPrag=INLINE (sat-args=0)]
:: forall val (cmeta :: Meta) (smeta :: Meta).
GBuild val (C1 cmeta (S1 smeta (Rec0 val)))
[GblId[DFunId(nt)],
Arity=1,
Caf=NoCafRefs,
Str=<L,U>m2,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=False,boring_ok=True)
Tmpl= Main.$fGBuildvalM10_$cgbuild
`cast` (forall (val :: <*>_N) (cmeta :: <Meta>_N) (smeta :: <Meta>_N).
Sym (Main.N:GBuild[0] <val>_N <C1 cmeta (S1 smeta (Rec0 val))>_N)
:: (forall val (cmeta :: Meta) (smeta :: Meta) x.
val -> [C1 cmeta (S1 smeta (Rec0 val)) x])
~R# (forall val (cmeta :: Meta) (smeta :: Meta).
GBuild val (C1 cmeta (S1 smeta (Rec0 val)))))}]
Main.$fGBuildvalM10
= Main.$fGBuildvalM10_$cgbuild
`cast` (forall (val :: <*>_N) (cmeta :: <Meta>_N) (smeta :: <Meta>_N).
Sym (Main.N:GBuild[0] <val>_N <C1 cmeta (S1 smeta (Rec0 val))>_N)
:: (forall val (cmeta :: Meta) (smeta :: Meta) x.
val -> [C1 cmeta (S1 smeta (Rec0 val)) x])
~R# (forall val (cmeta :: Meta) (smeta :: Meta).
GBuild val (C1 cmeta (S1 smeta (Rec0 val)))))
-- RHS size: {terms: 1, types: 0, coercions: 17, joins: 0/0}
Main.$fGBuildvalM1 [InlPrag=INLINE (sat-args=0)]
:: forall val (cmeta :: Meta) (sels :: * -> *).
GBuild val (C1 cmeta sels)
[GblId[DFunId(nt)],
Arity=1,
Caf=NoCafRefs,
Str=<L,A>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=0,unsat_ok=False,boring_ok=True)
Tmpl= Main.$fGBuildvalM1_$cgbuild
`cast` (forall (val :: <*>_N) (cmeta :: <Meta>_N) (sels :: <*
-> *>_N).
Sym (Main.N:GBuild[0] <val>_N <C1 cmeta sels>_N)
:: (forall val (cmeta :: Meta) (sels :: * -> *) x.
val -> [C1 cmeta sels x])
~R# (forall val (cmeta :: Meta) (sels :: * -> *).
GBuild val (C1 cmeta sels)))}]
Main.$fGBuildvalM1
= Main.$fGBuildvalM1_$cgbuild
`cast` (forall (val :: <*>_N) (cmeta :: <Meta>_N) (sels :: <*
-> *>_N).
Sym (Main.N:GBuild[0] <val>_N <C1 cmeta sels>_N)
:: (forall val (cmeta :: Meta) (sels :: * -> *) x.
val -> [C1 cmeta sels x])
~R# (forall val (cmeta :: Meta) (sels :: * -> *).
GBuild val (C1 cmeta sels)))
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$fShowX5 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$fShowX5 = "A "#
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$fShowX4 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$fShowX4 = "B "#
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$fShowX3 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$fShowX3 = "C "#
-- RHS size: {terms: 112, types: 68, coercions: 0, joins: 0/0}
Main.$w$cshowsPrec [InlPrag=NOUSERINLINE[2]]
:: ghc-prim-0.6.1:GHC.Prim.Int# -> X -> String -> String
[GblId,
Arity=3,
Str=<L,U><S,1*U><L,U>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [0 482 0] 713 90}]
Main.$w$cshowsPrec
= \ (ww_s3Kb :: ghc-prim-0.6.1:GHC.Prim.Int#)
(w_s3K7 :: X)
(w1_s3K8 :: String) ->
case w_s3K7 of {
A b1_a1A1 ->
case ghc-prim-0.6.1:GHC.Prim.>=# ww_s3Kb 11# of {
__DEFAULT ->
ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX5
(case b1_a1A1 of { ghc-prim-0.6.1:GHC.Types.I# ww3_a30w ->
case GHC.Show.$wshowSignedInt 11# ww3_a30w w1_s3K8 of
{ (# ww5_a30z, ww6_a30A #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww5_a30z ww6_a30A
}
});
1# ->
ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)4
(ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX5
(case b1_a1A1 of { ghc-prim-0.6.1:GHC.Types.I# ww3_a30w ->
case GHC.Show.$wshowSignedInt
11#
ww3_a30w
(ghc-prim-0.6.1:GHC.Types.: @ Char GHC.Show.$fShow(,)2 w1_s3K8)
of
{ (# ww5_a30z, ww6_a30A #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww5_a30z ww6_a30A
}
}))
};
B b1_a2kH ->
case ghc-prim-0.6.1:GHC.Prim.>=# ww_s3Kb 11# of {
__DEFAULT ->
ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX4
(ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)3
(GHC.Show.showLitString
b1_a2kH
(ghc-prim-0.6.1:GHC.Types.: @ Char GHC.Show.$fShow(,)3 w1_s3K8)));
1# ->
ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)4
(ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX4
(ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)3
(GHC.Show.showLitString
b1_a2kH
(ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)3
(ghc-prim-0.6.1:GHC.Types.: @ Char GHC.Show.$fShow(,)2 w1_s3K8)))))
};
C b1_a2kJ ->
case ghc-prim-0.6.1:GHC.Prim.>=# ww_s3Kb 11# of {
__DEFAULT ->
ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX3
(case b1_a2kJ of { ghc-prim-0.6.1:GHC.Types.I# ww3_a30w ->
case GHC.Show.$wshowSignedInt 11# ww3_a30w w1_s3K8 of
{ (# ww5_a30z, ww6_a30A #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww5_a30z ww6_a30A
}
});
1# ->
ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.$fShow(,)4
(ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
Main.$fShowX3
(case b1_a2kJ of { ghc-prim-0.6.1:GHC.Types.I# ww3_a30w ->
case GHC.Show.$wshowSignedInt
11#
ww3_a30w
(ghc-prim-0.6.1:GHC.Types.: @ Char GHC.Show.$fShow(,)2 w1_s3K8)
of
{ (# ww5_a30z, ww6_a30A #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww5_a30z ww6_a30A
}
}))
}
}
-- RHS size: {terms: 10, types: 5, coercions: 0, joins: 0/0}
Main.$fShowX_$cshowsPrec [InlPrag=NOUSERINLINE[2]]
:: Int -> X -> ShowS
[GblId,
Arity=3,
Str=<S,1*U(U)><S,1*U><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False)
Tmpl= \ (w_s3K6 [Occ=Once!] :: Int)
(w1_s3K7 [Occ=Once] :: X)
(w2_s3K8 [Occ=Once] :: String) ->
case w_s3K6 of { ghc-prim-0.6.1:GHC.Types.I# ww1_s3Kb [Occ=Once] ->
Main.$w$cshowsPrec ww1_s3Kb w1_s3K7 w2_s3K8
}}]
Main.$fShowX_$cshowsPrec
= \ (w_s3K6 :: Int) (w1_s3K7 :: X) (w2_s3K8 :: String) ->
case w_s3K6 of { ghc-prim-0.6.1:GHC.Types.I# ww1_s3Kb ->
Main.$w$cshowsPrec ww1_s3Kb w1_s3K7 w2_s3K8
}
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$fShowX2 :: Int
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$fShowX2 = ghc-prim-0.6.1:GHC.Types.I# 0#
-- RHS size: {terms: 5, types: 2, coercions: 0, joins: 0/0}
Main.$fShowX_$cshow :: X -> String
[GblId,
Arity=1,
Str=<S,1*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=False)
Tmpl= \ (x_a2R9 [Occ=Once] :: X) ->
Main.$fShowX_$cshowsPrec
Main.$fShowX2 x_a2R9 (ghc-prim-0.6.1:GHC.Types.[] @ Char)}]
Main.$fShowX_$cshow
= \ (x_a2R9 :: X) ->
Main.$w$cshowsPrec 0# x_a2R9 (ghc-prim-0.6.1:GHC.Types.[] @ Char)
-- RHS size: {terms: 6, types: 2, coercions: 0, joins: 0/0}
Main.$fShowX1 :: X -> ShowS
[GblId,
Arity=2,
Str=<S,1*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=False)
Tmpl= Main.$fShowX_$cshowsPrec Main.$fShowX2}]
Main.$fShowX1
= \ (w_s3K7 :: X) (w1_s3K8 :: String) ->
Main.$w$cshowsPrec 0# w_s3K7 w1_s3K8
-- RHS size: {terms: 6, types: 4, coercions: 0, joins: 0/0}
Main.$fShowX_$cshowList :: [X] -> ShowS
[GblId,
Arity=2,
Str=<S,1*U><L,U>,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
Tmpl= \ (ls_a2Rc [Occ=Once] :: [X])
(s_a2Rd [Occ=Once] :: String) ->
GHC.Show.showList__ @ X Main.$fShowX1 ls_a2Rc s_a2Rd}]
Main.$fShowX_$cshowList
= \ (ls_a2Rc :: [X]) (s_a2Rd :: String) ->
GHC.Show.showList__ @ X Main.$fShowX1 ls_a2Rc s_a2Rd
-- RHS size: {terms: 4, types: 1, coercions: 0, joins: 0/0}
Main.$fShowX [InlPrag=NOUSERINLINE CONLIKE] :: Show X
[GblId[DFunId],
Str=m,
Unf=DFun: \ ->
GHC.Show.C:Show TYPE: X
Main.$fShowX_$cshowsPrec
Main.$fShowX_$cshow
Main.$fShowX_$cshowList]
Main.$fShowX
= GHC.Show.C:Show
@ X
Main.$fShowX_$cshowsPrec
Main.$fShowX_$cshow
Main.$fShowX_$cshowList
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$trModule4 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$trModule4 = "main"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$trModule3 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$trModule3 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$trModule4
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$trModule2 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$trModule2 = "Main"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$trModule1 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$trModule1 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$trModule2
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
Main.$trModule :: ghc-prim-0.6.1:GHC.Types.Module
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
Main.$trModule
= ghc-prim-0.6.1:GHC.Types.Module Main.$trModule3 Main.$trModule1
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep_r3Or :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1, Unf=OtherCon []]
$krep_r3Or
= ghc-prim-0.6.1:GHC.Types.KindRepTyConApp
ghc-prim-0.6.1:GHC.Types.$tcChar
(ghc-prim-0.6.1:GHC.Types.[] @ ghc-prim-0.6.1:GHC.Types.KindRep)
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep1_r3Os :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1, Unf=OtherCon []]
$krep1_r3Os
= ghc-prim-0.6.1:GHC.Types.KindRepTyConApp
ghc-prim-0.6.1:GHC.Types.$tcInt
(ghc-prim-0.6.1:GHC.Types.[] @ ghc-prim-0.6.1:GHC.Types.KindRep)
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep2_r3Ot :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1, Unf=OtherCon []]
$krep2_r3Ot
= ghc-prim-0.6.1:GHC.Types.KindRepTyConApp
ghc-prim-0.6.1:GHC.Types.$tcConstraint
(ghc-prim-0.6.1:GHC.Types.[] @ ghc-prim-0.6.1:GHC.Types.KindRep)
-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
$krep3_r3Ou :: [ghc-prim-0.6.1:GHC.Types.KindRep]
[GblId, Caf=NoCafRefs, Str=m2, Unf=OtherCon []]
$krep3_r3Ou
= ghc-prim-0.6.1:GHC.Types.:
@ ghc-prim-0.6.1:GHC.Types.KindRep
$krep_r3Or
(ghc-prim-0.6.1:GHC.Types.[] @ ghc-prim-0.6.1:GHC.Types.KindRep)
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep4_r3Ov :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1, Unf=OtherCon []]
$krep4_r3Ov
= ghc-prim-0.6.1:GHC.Types.KindRepTyConApp
ghc-prim-0.6.1:GHC.Types.$tc[] $krep3_r3Ou
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep5_r3Ow :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m4, Unf=OtherCon []]
$krep5_r3Ow
= ghc-prim-0.6.1:GHC.Types.KindRepFun
ghc-prim-0.6.1:GHC.Types.krep$*Arr* $krep2_r3Ot
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
Main.$tcGBuild1 [InlPrag=NOUSERINLINE[~]]
:: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m4, Unf=OtherCon []]
Main.$tcGBuild1
= ghc-prim-0.6.1:GHC.Types.KindRepFun
ghc-prim-0.6.1:GHC.Types.krep$* $krep5_r3Ow
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$tcX2 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$tcX2 = "X"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$tcX1 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$tcX1 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$tcX2
-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
Main.$tcX :: ghc-prim-0.6.1:GHC.Types.TyCon
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
Main.$tcX
= ghc-prim-0.6.1:GHC.Types.TyCon
6136962148358085538##
2047526523769221729##
Main.$trModule
Main.$tcX1
0#
ghc-prim-0.6.1:GHC.Types.krep$*
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep6_r3Ox :: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1, Unf=OtherCon []]
$krep6_r3Ox
= ghc-prim-0.6.1:GHC.Types.KindRepTyConApp
Main.$tcX
(ghc-prim-0.6.1:GHC.Types.[] @ ghc-prim-0.6.1:GHC.Types.KindRep)
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
Main.$tc'B1 [InlPrag=NOUSERINLINE[~]]
:: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m4, Unf=OtherCon []]
Main.$tc'B1
= ghc-prim-0.6.1:GHC.Types.KindRepFun $krep4_r3Ov $krep6_r3Ox
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$tc'B3 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$tc'B3 = "'B"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$tc'B2 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$tc'B2 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$tc'B3
-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
Main.$tc'B :: ghc-prim-0.6.1:GHC.Types.TyCon
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
Main.$tc'B
= ghc-prim-0.6.1:GHC.Types.TyCon
5204529440822741764##
15433236706311297883##
Main.$trModule
Main.$tc'B2
0#
Main.$tc'B1
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
Main.$tc'A1 [InlPrag=NOUSERINLINE[~]]
:: ghc-prim-0.6.1:GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m4, Unf=OtherCon []]
Main.$tc'A1
= ghc-prim-0.6.1:GHC.Types.KindRepFun $krep1_r3Os $krep6_r3Ox
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$tc'A3 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$tc'A3 = "'A"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$tc'A2 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$tc'A2 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$tc'A3
-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
Main.$tc'A :: ghc-prim-0.6.1:GHC.Types.TyCon
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
Main.$tc'A
= ghc-prim-0.6.1:GHC.Types.TyCon
693283182868825203##
17013768436588654685##
Main.$trModule
Main.$tc'A2
0#
Main.$tc'A1
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$tc'C2 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
Main.$tc'C2 = "'C"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$tc'C1 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$tc'C1 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$tc'C2
-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
Main.$tc'C :: ghc-prim-0.6.1:GHC.Types.TyCon
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
Main.$tc'C
= ghc-prim-0.6.1:GHC.Types.TyCon
10502984155413422402##
772885320322164953##
Main.$trModule
Main.$tc'C1
0#
Main.$tc'A1
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
Main.$tcGBuild3 :: ghc-prim-0.6.1:GHC.Prim.Addr#
[GblId,
Caf=NoCafRefs,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
Main.$tcGBuild3 = "GBuild"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.$tcGBuild2 :: ghc-prim-0.6.1:GHC.Types.TrName
[GblId,
Caf=NoCafRefs,
Str=m1,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.$tcGBuild2 = ghc-prim-0.6.1:GHC.Types.TrNameS Main.$tcGBuild3
-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
Main.$tcGBuild :: ghc-prim-0.6.1:GHC.Types.TyCon
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
Main.$tcGBuild
= ghc-prim-0.6.1:GHC.Types.TyCon
5701242119193077577##
531234132182018271##
Main.$trModule
Main.$tcGBuild2
0#
Main.$tcGBuild1
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
Main.values4 :: Int
[GblId,
Caf=NoCafRefs,
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
Main.values4 = ghc-prim-0.6.1:GHC.Types.I# 10#
-- RHS size: {terms: 3, types: 44, coercions: 52, joins: 0/0}
Main.values5
:: [C1
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any]
[GblId,
Caf=NoCafRefs,
Str=m2,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
Main.values5
= ghc-prim-0.6.1:GHC.Types.:
@ (C1
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any)
(Main.values4
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<ghc-prim-0.6.1:GHC.Types.Any>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"A"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <ghc-prim-0.6.1:GHC.Types.Any>_N
:: Int
~R# M1
C
('MetaCons "A" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
ghc-prim-0.6.1:GHC.Types.Any))
(ghc-prim-0.6.1:GHC.Types.[]
@ (C1
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any))
-- RHS size: {terms: 3, types: 44, coercions: 52, joins: 0/0}
Main.values3
:: [C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any]
[GblId,
Caf=NoCafRefs,
Str=m2,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
Main.values3
= ghc-prim-0.6.1:GHC.Types.:
@ (C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any)
(Main.values4
`cast` (Sym (GHC.Generics.N:K1[0]
<*>_N
<R>_P
<Int>_R
<ghc-prim-0.6.1:GHC.Types.Any>_P) ; (Sym (GHC.Generics.N:M1[0]
<*>_N
<S>_P
<'MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy>_P
<K1
R
Int>_R) ; Sym (GHC.Generics.N:M1[0]
<*>_N
<C>_P
<'MetaCons
"C"
'PrefixI
'False>_P
<M1
S
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(K1
R
Int)>_R)) <ghc-prim-0.6.1:GHC.Types.Any>_N
:: Int
~R# M1
C
('MetaCons "C" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(K1 R Int))
ghc-prim-0.6.1:GHC.Types.Any))
(ghc-prim-0.6.1:GHC.Types.[]
@ (C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any))
-- RHS size: {terms: 3, types: 101, coercions: 0, joins: 0/0}
Main.values2
:: [(:+:)
(M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
(M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any]
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 30 0}]
Main.values2
= map
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any)
@ ((:+:)
(M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
(M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ ghc-prim-0.6.1:GHC.Types.Any)
Main.values3
-- RHS size: {terms: 7, types: 318, coercions: 0, joins: 0/0}
Main.values1
:: [(:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any]
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 90 0}]
Main.values1
= map
@ ((:+:)
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
(C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
@ ((:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(GHC.Generics.R1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ (C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ ghc-prim-0.6.1:GHC.Types.Any)
(++
@ ((:+:)
(M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
(M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(map
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
ghc-prim-0.6.1:GHC.Types.Any)
@ ((:+:)
(M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
(M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)))
@ (M1
C
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ ghc-prim-0.6.1:GHC.Types.Any)
(ghc-prim-0.6.1:GHC.Types.[]
@ (C1
('MetaCons "B" 'PrefixI 'False)
(M1
S
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
ghc-prim-0.6.1:GHC.Types.Any)))
Main.values2)
-- RHS size: {terms: 7, types: 203, coercions: 79, joins: 0/0}
values [InlPrag=NOINLINE[1]] :: [X]
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 90 0}]
values
= map
@ (Rep X ghc-prim-0.6.1:GHC.Types.Any)
@ X
(Main.$fGenericX_$cto @ ghc-prim-0.6.1:GHC.Types.Any)
((++
@ ((:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(map
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
ghc-prim-0.6.1:GHC.Types.Any)
@ ((:+:)
(M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any)
(GHC.Generics.L1
@ *
@ (M1
C
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ (C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
@ ghc-prim-0.6.1:GHC.Types.Any)
Main.values5)
Main.values1)
`cast` (([Sym (GHC.Generics.N:M1[0]
<*>_N
<D>_P
<'MetaData "X" "Main" "main" 'False>_P
<C1
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int))
:+: (C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing
'NoSourceUnpackedness
'NoSourceStrictness
'DecidedLazy)
(Rec0 Int)))>_R) <ghc-prim-0.6.1:GHC.Types.Any>_N ; Nth:0
(Nth:3
(<Int>_R
->_R ([Sub (Sym (Main.D:R:RepX[0])) <ghc-prim-0.6.1:GHC.Types.Any>_N])_R))])_R
:: [(:+:)
(C1
('MetaCons "A" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
(C1
('MetaCons "B" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String))
:+: C1
('MetaCons "C" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)))
ghc-prim-0.6.1:GHC.Types.Any]
~R# [Rep X ghc-prim-0.6.1:GHC.Types.Any]))
Rec {
-- RHS size: {terms: 8, types: 12, coercions: 0, joins: 0/0}
Main.main_showl [InlPrag=NOUSERINLINE[2]] :: [X] -> String
[GblId,
Arity=1,
Str=<S,1*U>m2,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True,
Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
Tmpl= \ (w_s3Ke [Occ=Once] :: [X]) ->
case Main.$wshowl w_s3Ke of
{ (# ww1_s3Kj [Occ=Once], ww2_s3Kk [Occ=Once] #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww1_s3Kj ww2_s3Kk
}}]
Main.main_showl
= \ (w_s3Ke :: [X]) ->
case Main.$wshowl w_s3Ke of { (# ww1_s3Kj, ww2_s3Kk #) ->
ghc-prim-0.6.1:GHC.Types.: @ Char ww1_s3Kj ww2_s3Kk
}
-- RHS size: {terms: 15, types: 18, coercions: 0, joins: 0/0}
Main.$wshowl [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker]
:: [X] -> (# Char, [Char] #)
[GblId, Arity=1, Str=<S,1*U>, Unf=OtherCon []]
Main.$wshowl
= \ (w_s3Ke :: [X]) ->
case w_s3Ke of {
[] ->
(# GHC.Show.showList__2, ghc-prim-0.6.1:GHC.Types.[] @ Char #);
: y_a317 ys_a318 ->
(# GHC.Show.showList__1,
Main.$w$cshowsPrec 0# y_a317 (Main.main_showl ys_a318) #)
}
end Rec }
-- RHS size: {terms: 14, types: 7, coercions: 0, joins: 0/0}
Main.main1 :: String
[GblId,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False,
WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 120 30}]
Main.main1
= case values of {
[] ->
ghc-prim-0.6.1:GHC.CString.unpackAppendCString#
GHC.Show.showList__4 (ghc-prim-0.6.1:GHC.Types.[] @ Char);
: x_a30Z xs_a310 ->
ghc-prim-0.6.1:GHC.Types.:
@ Char
GHC.Show.showList__3
(Main.$w$cshowsPrec 0# x_a30Z (Main.main_showl xs_a310))
}
-- RHS size: {terms: 4, types: 0, coercions: 0, joins: 0/0}
main :: IO ()
[GblId,
Arity=1,
Str=<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=False)
Tmpl= GHC.IO.Handle.Text.hPutStr'
GHC.IO.Handle.FD.stdout Main.main1 ghc-prim-0.6.1:GHC.Types.True}]
main
= GHC.IO.Handle.Text.hPutStr'
GHC.IO.Handle.FD.stdout Main.main1 ghc-prim-0.6.1:GHC.Types.True
-- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
Main.main2
:: ghc-prim-0.6.1:GHC.Prim.State# ghc-prim-0.6.1:GHC.Prim.RealWorld
-> (# ghc-prim-0.6.1:GHC.Prim.State#
ghc-prim-0.6.1:GHC.Prim.RealWorld,
() #)
[GblId,
Arity=1,
Str=<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=False)
Tmpl= GHC.TopHandler.runMainIO1 @ () main}]
Main.main2 = GHC.TopHandler.runMainIO1 @ () main
-- RHS size: {terms: 1, types: 0, coercions: 3, joins: 0/0}
:Main.main :: IO ()
[GblId,
Arity=1,
Str=<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= Main.main2
`cast` (Sym (ghc-prim-0.6.1:GHC.Types.N:IO[0] <()>_R)
:: (ghc-prim-0.6.1:GHC.Prim.State#
ghc-prim-0.6.1:GHC.Prim.RealWorld
-> (# ghc-prim-0.6.1:GHC.Prim.State#
ghc-prim-0.6.1:GHC.Prim.RealWorld,
() #))
~R# IO ())}]
:Main.main
= Main.main2
`cast` (Sym (ghc-prim-0.6.1:GHC.Types.N:IO[0] <()>_R)
:: (ghc-prim-0.6.1:GHC.Prim.State#
ghc-prim-0.6.1:GHC.Prim.RealWorld
-> (# ghc-prim-0.6.1:GHC.Prim.State#
ghc-prim-0.6.1:GHC.Prim.RealWorld,
() #))
~R# IO ())
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment