Skip to content

Instantly share code, notes, and snippets.

@soupi
Last active February 1, 2020 06:45
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 soupi/ee85d03775c21ad2f9270062deeb1b80 to your computer and use it in GitHub Desktop.
Save soupi/ee85d03775c21ad2f9270062deeb1b80 to your computer and use it in GitHub Desktop.
Plate.hs src
-- stack exec --package uniplate --package criterion -- ghc Plate.hs -O2 -ddump-simpl -dsuppress-all > /tmp/Plate-dump.hs
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
import GHC.Generics
import Transform
data Expr
= Lit Int
| Add Expr Expr
| Mul Expr Expr
| Div Expr Expr
| Sub Expr Expr
| Neg Expr
deriving (Generic)
opts :: Expr -> Expr
opts = \case
Add (Lit 0) e -> e
Add e (Lit 0) -> e
Mul (Lit 1) e -> e
Mul e (Lit 1) -> e
Mul (Lit 0) _ -> Lit 0
Mul _ (Lit 0) -> Lit 0
Neg (Neg e) -> e
e -> e
foo :: Expr
foo = Add (Lit 0) (Lit 1)
{-# noinline foo #-}
main = do
pure $ transformBi opts foo
@soupi
Copy link
Author

soupi commented Jan 31, 2020

Transform.hs

{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, UndecidableInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MonoLocalBinds #-}

module Transform where

import GHC.Generics

  
---------------
-- Transform --
---------------

-- GTransform --

class GTransform a struct where
  gtransform :: (a -> a) -> struct x -> struct x

instance GTransform a U1 where
  gtransform _ U1 = U1
  {-# inline gtransform #-}

instance GTransform a V1 where
  gtransform _ x = x
  {-# inline gtransform #-}

instance {-# OVERLAPPING #-} TransformRec a a => GTransform a (Rec0 a) where
  gtransform f (K1 a) = K1 (f $ transformRec f a)
  {-# inline gtransform #-}

instance TransformRec a b => GTransform a (K1 _1 b) where
  gtransform f (K1 b) = K1 (transformRec f b)
  {-# inline gtransform #-}

instance (GTransform a x, GTransform a y) => GTransform a (x :+: y) where
  gtransform f = \case
    L1 x -> L1 $ gtransform f x
    R1 y -> R1 $ gtransform f y
  {-# inline gtransform #-}

instance (GTransform a x, GTransform a y) => GTransform a (x :*: y) where
  gtransform f (x :*: y) = gtransform f x :*: gtransform f y
  {-# inline gtransform #-}

instance GTransform a struct => GTransform a (M1 _x _y struct) where
  gtransform f (M1 a) = M1 $ gtransform f a
  {-# inline gtransform #-}

-- TransformRec --

class TransformRec a x where
  transformRec :: (a -> a) -> x -> x
  default transformRec :: Generic x => GTransform a (Rep x) => (a -> a) -> x -> x
  transformRec f x = to (gtransform f (from x))
  {-# inline transformRec #-}

instance {-# OVERLAPPING #-} (Generic b, GTransform a (Rep b)) => TransformRec a b where
  transformRec f x = to (gtransform f (from x))
  {-# inline transformRec #-}

instance {-# overlapping #-} TransformRec a Int where
  transformRec f x = x
  {-# inline transformRec #-}

-- TransformBi --

class TransformBi a x where
  transformBi :: (a -> a) -> x -> x
  default transformBi :: Generic x => GTransform a (Rep x) => (a -> a) -> x -> x
  transformBi f x = to (gtransform f (from x))
  {-# inline transformBi #-}

instance {-# overlapping #-} (Generic x, GTransform x (Rep x)) => TransformBi x x where
  transformBi f x = f (to (gtransform f (from x)))
  {-# inline transformBi #-}

instance {-# overlapping #-} (Generic x, GTransform a (Rep x)) => TransformBi a x

@soupi
Copy link
Author

soupi commented Feb 1, 2020

[1 of 2] Compiling Transform        ( Transform.hs, Transform.o )

==================== Tidy Core ====================
Result size of Tidy Core
  = {terms: 346, types: 835, coercions: 359, joins: 0/0}

-- RHS size: {terms: 4, types: 7, coercions: 3, joins: 0/0}
transformBi
transformBi = \ @ a_a1o4 @ x_a1o5 v_B1 -> v_B1 `cast` <Co:3>

-- RHS size: {terms: 4, types: 7, coercions: 3, joins: 0/0}
transformRec
transformRec = \ @ a_a1o8 @ x_a1o9 v_B1 -> v_B1 `cast` <Co:3>

-- RHS size: {terms: 4, types: 9, coercions: 3, joins: 0/0}
gtransform
gtransform = \ @ a_a1oc @ struct_a1od v_B1 -> v_B1 `cast` <Co:3>

-- RHS size: {terms: 5, types: 10, coercions: 0, joins: 0/0}
$fGTransformaU1_$cgtransform
$fGTransformaU1_$cgtransform
  = \ @ a_a2w2 @ x_a2w6 _ ds1_d2yH -> ds1_d2yH

-- RHS size: {terms: 1, types: 0, coercions: 9, joins: 0/0}
$fGTransformaU1
$fGTransformaU1 = $fGTransformaU1_$cgtransform `cast` <Co:9>

-- RHS size: {terms: 5, types: 10, coercions: 0, joins: 0/0}
$fGTransformaV1_$cgtransform
$fGTransformaV1_$cgtransform
  = \ @ a_a2vU @ x_a2vY _ x1_a1Sz -> x1_a1Sz

-- RHS size: {terms: 1, types: 0, coercions: 9, joins: 0/0}
$fGTransformaV1
$fGTransformaV1 = $fGTransformaV1_$cgtransform `cast` <Co:9>

-- RHS size: {terms: 20, types: 48, coercions: 6, joins: 0/0}
$fGTransforma:+:_$cgtransform
$fGTransforma:+:_$cgtransform
  = \ @ a_a2vl
      @ x_a2vm
      @ y_a2vn
      $dGTransform_a2vo
      $dGTransform1_a2vp
      @ x1_a2vt
      eta_B1
      ds_d2yw ->
      case ds_d2yw of {
        L1 x2_a1So ->
          L1 (($dGTransform_a2vo `cast` <Co:3>) eta_B1 x2_a1So);
        R1 y1_a1Sp ->
          R1 (($dGTransform1_a2vp `cast` <Co:3>) eta_B1 y1_a1Sp)
      }

-- RHS size: {terms: 1, types: 0, coercions: 29, joins: 0/0}
$fGTransforma:+:
$fGTransforma:+: = $fGTransforma:+:_$cgtransform `cast` <Co:29>

-- RHS size: {terms: 18, types: 43, coercions: 6, joins: 0/0}
$fGTransforma:*:_$cgtransform
$fGTransforma:*:_$cgtransform
  = \ @ a_a2uV
      @ x_a2uW
      @ y_a2uX
      $dGTransform_a2uY
      $dGTransform1_a2uZ
      @ x1_a2v3
      eta_B2
      eta1_B1 ->
      case eta1_B1 of { :*: x2_a1Si y1_a1Sj ->
      :*:
        (($dGTransform_a2uY `cast` <Co:3>) eta_B2 x2_a1Si)
        (($dGTransform1_a2uZ `cast` <Co:3>) eta_B2 y1_a1Sj)
      }

-- RHS size: {terms: 1, types: 0, coercions: 29, joins: 0/0}
$fGTransforma:*:
$fGTransforma:*: = $fGTransforma:*:_$cgtransform `cast` <Co:29>

-- RHS size: {terms: 11, types: 23, coercions: 10, joins: 0/0}
$cgtransform_r2AF
$cgtransform_r2AF
  = \ @ a_a2uw
      @ struct_a2ux
      @ _x_a2uy
      @ _y_a2uz
      $dGTransform_a2uA
      @ x_a2uE
      eta_B2
      eta1_B1 ->
      ($dGTransform_a2uA `cast` <Co:3>) eta_B2 (eta1_B1 `cast` <Co:7>)

-- RHS size: {terms: 1, types: 0, coercions: 38, joins: 0/0}
$fGTransformaM1_$cgtransform
$fGTransformaM1_$cgtransform = $cgtransform_r2AF `cast` <Co:38>

-- RHS size: {terms: 1, types: 0, coercions: 25, joins: 0/0}
$fGTransformaM1
$fGTransformaM1 = $fGTransformaM1_$cgtransform `cast` <Co:25>

-- RHS size: {terms: 9, types: 15, coercions: 9, joins: 0/0}
$cgtransform1_r2AG
$cgtransform1_r2AG
  = \ @ a_a2u9 $dTransformRec_a2ua @ x_a2ue eta_X17 eta1_X2d ->
      eta_X17
        (($dTransformRec_a2ua `cast` <Co:3>)
           eta_X17 (eta1_X2d `cast` <Co:6>))

-- RHS size: {terms: 1, types: 0, coercions: 27, joins: 0/0}
$fGTransformaK10_$cgtransform
$fGTransformaK10_$cgtransform = $cgtransform1_r2AG `cast` <Co:27>

-- RHS size: {terms: 1, types: 0, coercions: 14, joins: 0/0}
$fGTransformaK10
$fGTransformaK10 = $fGTransformaK10_$cgtransform `cast` <Co:14>

-- RHS size: {terms: 10, types: 18, coercions: 9, joins: 0/0}
$cgtransform2_r2AH
$cgtransform2_r2AH
  = \ @ a_a2tP
      @ b_a2tQ
      @ _1_a2tR
      $dTransformRec_a2tS
      @ x_a2tW
      eta_X1h
      eta1_X2x ->
      ($dTransformRec_a2tS `cast` <Co:3>)
        eta_X1h (eta1_X2x `cast` <Co:6>)

-- RHS size: {terms: 1, types: 0, coercions: 32, joins: 0/0}
$fGTransformaK1_$cgtransform
$fGTransformaK1_$cgtransform = $cgtransform2_r2AH `cast` <Co:32>

-- RHS size: {terms: 1, types: 0, coercions: 20, joins: 0/0}
$fGTransformaK1
$fGTransformaK1 = $fGTransformaK1_$cgtransform `cast` <Co:20>

-- RHS size: {terms: 13, types: 21, coercions: 4, joins: 0/0}
$fTransformRecab_$ctransformRec
$fTransformRecab_$ctransformRec
  = \ @ b_a2tt
      @ a_a2tu
      $dGeneric_a2tv
      $dGTransform_a2tw
      eta_X1q
      eta1_X2P ->
      to
        $dGeneric_a2tv
        (($dGTransform_a2tw `cast` <Co:4>)
           eta_X1q (from $dGeneric_a2tv eta1_X2P))

-- RHS size: {terms: 1, types: 0, coercions: 18, joins: 0/0}
$fTransformRecab
$fTransformRecab = $fTransformRecab_$ctransformRec `cast` <Co:18>

-- RHS size: {terms: 4, types: 5, coercions: 0, joins: 0/0}
$fTransformRecaInt_$ctransformRec
$fTransformRecaInt_$ctransformRec = \ @ a_a2tm _ x_a1S3 -> x_a1S3

-- RHS size: {terms: 1, types: 0, coercions: 7, joins: 0/0}
$fTransformRecaInt
$fTransformRecaInt
  = $fTransformRecaInt_$ctransformRec `cast` <Co:7>

-- RHS size: {terms: 13, types: 19, coercions: 4, joins: 0/0}
$fTransformBixx_$ctransformBi
$fTransformBixx_$ctransformBi
  = \ @ x_a2t1 $dGeneric_a2t2 $dGTransform_a2t3 eta_X1t eta1_X2V ->
      eta_X1t
        (to
           $dGeneric_a2t2
           (($dGTransform_a2t3 `cast` <Co:4>)
              eta_X1t (from $dGeneric_a2t2 eta1_X2V)))

-- RHS size: {terms: 1, types: 0, coercions: 15, joins: 0/0}
$fTransformBixx
$fTransformBixx = $fTransformBixx_$ctransformBi `cast` <Co:15>

-- RHS size: {terms: 14, types: 24, coercions: 4, joins: 0/0}
$dmtransformBi
$dmtransformBi
  = \ @ a_a1o4
      @ x_a1o5
      _
      $dGeneric_a2sw
      $dGTransform_a2sx
      f_a1o6
      x1_a1o7 ->
      to
        $dGeneric_a2sw
        (($dGTransform_a2sx `cast` <Co:4>)
           f_a1o6 (from $dGeneric_a2sw x1_a1o7))

-- RHS size: {terms: 13, types: 21, coercions: 4, joins: 0/0}
$fTransformBiax_$ctransformBi
$fTransformBiax_$ctransformBi
  = \ @ x_a2sM
      @ a_a2sN
      $dGeneric_a2sO
      $dGTransform_a2sP
      eta_X1y
      eta1_X35 ->
      to
        $dGeneric_a2sO
        (($dGTransform_a2sP `cast` <Co:4>)
           eta_X1y (from $dGeneric_a2sO eta1_X35))

-- RHS size: {terms: 1, types: 0, coercions: 18, joins: 0/0}
$fTransformBiax
$fTransformBiax = $fTransformBiax_$ctransformBi `cast` <Co:18>

-- RHS size: {terms: 14, types: 24, coercions: 4, joins: 0/0}
$dmtransformRec
$dmtransformRec
  = \ @ a_a1o8
      @ x_a1o9
      _
      $dGeneric_a2sb
      $dGTransform_a2sc
      f_a1oa
      x1_a1ob ->
      to
        $dGeneric_a2sb
        (($dGTransform_a2sc `cast` <Co:4>)
           f_a1oa (from $dGeneric_a2sb x1_a1ob))

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule4
$trModule4 = "main"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule3
$trModule3 = TrNameS $trModule4

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule2
$trModule2 = "Transform"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule1
$trModule1 = TrNameS $trModule2

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$trModule
$trModule = Module $trModule3 $trModule1

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep_r2AI
$krep_r2AI = KindRepTyConApp $tcConstraint []

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep1_r2AJ
$krep1_r2AJ = KindRepFun krep$* $krep_r2AI

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tcTransformBi1
$tcTransformBi1 = KindRepFun krep$* $krep1_r2AJ

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep2_r2AK
$krep2_r2AK = KindRepFun krep$*Arr* $krep_r2AI

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tcGTransform1
$tcGTransform1 = KindRepFun krep$* $krep2_r2AK

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$krep3_r2AL
$krep3_r2AL = KindRepVar 1#

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep4_r2AM
$krep4_r2AM = KindRepFun $krep3_r2AL $krep3_r2AL

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$krep5_r2AN
$krep5_r2AN = KindRepVar 0#

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep6_r2AO
$krep6_r2AO = KindRepFun $krep5_r2AN $krep5_r2AN

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep7_r2AP
$krep7_r2AP = KindRepFun $krep6_r2AO $krep4_r2AM

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcGTransform3
$tcGTransform3 = "GTransform"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcGTransform2
$tcGTransform2 = TrNameS $tcGTransform3

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tcGTransform
$tcGTransform
  = TyCon
      18223861616190018618##
      5784081840464734388##
      $trModule
      $tcGTransform2
      0#
      $tcGTransform1

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcTransformRec2
$tcTransformRec2 = "TransformRec"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcTransformRec1
$tcTransformRec1 = TrNameS $tcTransformRec2

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tcTransformRec
$tcTransformRec
  = TyCon
      5837674720315456291##
      9054258452144006960##
      $trModule
      $tcTransformRec1
      0#
      $tcTransformBi1

-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
$krep8_r2AQ
$krep8_r2AQ = : $krep3_r2AL []

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep9_r2AR
$krep9_r2AR = : $krep5_r2AN $krep8_r2AQ

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep10_r2AS
$krep10_r2AS = KindRepTyConApp $tcTransformRec $krep9_r2AR

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformRec1
$tc'C:TransformRec1 = KindRepFun $krep7_r2AP $krep10_r2AS

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformRec3
$tc'C:TransformRec3 = "'C:TransformRec"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformRec2
$tc'C:TransformRec2 = TrNameS $tc'C:TransformRec3

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformRec
$tc'C:TransformRec
  = TyCon
      4955051758031584061##
      17511181468199869489##
      $trModule
      $tc'C:TransformRec2
      2#
      $tc'C:TransformRec1

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcTransformBi3
$tcTransformBi3 = "TransformBi"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcTransformBi2
$tcTransformBi2 = TrNameS $tcTransformBi3

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tcTransformBi
$tcTransformBi
  = TyCon
      11871789999325947604##
      7355603391471024635##
      $trModule
      $tcTransformBi2
      0#
      $tcTransformBi1

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$krep11_r2AT
$krep11_r2AT = KindRepTyConApp $tcTransformBi $krep9_r2AR

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformBi1
$tc'C:TransformBi1 = KindRepFun $krep7_r2AP $krep11_r2AT

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformBi3
$tc'C:TransformBi3 = "'C:TransformBi"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformBi2
$tc'C:TransformBi2 = TrNameS $tc'C:TransformBi3

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'C:TransformBi
$tc'C:TransformBi
  = TyCon
      13676485824907351666##
      8910929623244922938##
      $trModule
      $tc'C:TransformBi2
      2#
      $tc'C:TransformBi1



[2 of 2] Compiling Main             ( Plate.hs, Plate.o )

==================== Tidy Core ====================
Result size of Tidy Core
  = {terms: 525, types: 7,656, coercions: 3,329, joins: 2/2}

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Sub2
$tc'Sub2 = "'Sub"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Sub1
$tc'Sub1 = TrNameS $tc'Sub2

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Div2
$tc'Div2 = "'Div"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Div1
$tc'Div1 = TrNameS $tc'Div2

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Mul2
$tc'Mul2 = "'Mul"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Mul1
$tc'Mul1 = TrNameS $tc'Mul2

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Add3
$tc'Add3 = "'Add"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Add2
$tc'Add2 = TrNameS $tc'Add3

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Neg3
$tc'Neg3 = "'Neg"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Neg2
$tc'Neg2 = TrNameS $tc'Neg3

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tc'Lit3
$tc'Lit3 = "'Lit"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tc'Lit2
$tc'Lit2 = TrNameS $tc'Lit3

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$tcExpr2
$tcExpr2 = "Expr"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$tcExpr1
$tcExpr1 = TrNameS $tcExpr2

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep_r76W
$krep_r76W = KindRepTyConApp $tcInt []

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule2
$trModule2 = "Main"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule1
$trModule1 = TrNameS $trModule2

-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
$trModule4
$trModule4 = "main"#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
$trModule3
$trModule3 = TrNameS $trModule4

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$trModule
$trModule = Module $trModule3 $trModule1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tcExpr
$tcExpr
  = TyCon
      12091566065001353326##
      14673633334727774453##
      $trModule
      $tcExpr1
      0#
      krep$*

-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
$krep1_r76X
$krep1_r76X = KindRepTyConApp $tcExpr []

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tc'Lit1
$tc'Lit1 = KindRepFun $krep_r76W $krep1_r76X

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tc'Neg1
$tc'Neg1 = KindRepFun $krep1_r76X $krep1_r76X

-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
$tc'Add1
$tc'Add1 = KindRepFun $krep1_r76X $tc'Neg1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Lit
$tc'Lit
  = TyCon
      18167568965991756872##
      17650254380305224383##
      $trModule
      $tc'Lit2
      0#
      $tc'Lit1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Neg
$tc'Neg
  = TyCon
      7793560789665771617##
      16821389539079660119##
      $trModule
      $tc'Neg2
      0#
      $tc'Neg1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Add
$tc'Add
  = TyCon
      10832780695868222026##
      16344471105793923761##
      $trModule
      $tc'Add2
      0#
      $tc'Add1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Mul
$tc'Mul
  = TyCon
      14840184544315911395##
      10216988503268596648##
      $trModule
      $tc'Mul1
      0#
      $tc'Add1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Div
$tc'Div
  = TyCon
      11645750416555189232##
      3813003399367813461##
      $trModule
      $tc'Div1
      0#
      $tc'Add1

-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
$tc'Sub
$tc'Sub
  = TyCon
      2765520555454642545##
      4774318161135844476##
      $trModule
      $tc'Sub1
      0#
      $tc'Add1

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
main6
main6 = I# 0#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
main5
main5 = Lit main6

-- RHS size: {terms: 130, types: 55, coercions: 0, joins: 2/2}
main_f
main_f
  = \ ds_d5ef ->
      case ds_d5ef of wild_X1c {
        __DEFAULT -> wild_X1c;
        Add ds1_d5ir e_a2MX ->
          case ds1_d5ir of wild1_Xv {
            __DEFAULT ->
              case e_a2MX of {
                __DEFAULT -> wild_X1c;
                Lit ds2_d5iu ->
                  case ds2_d5iu of { I# ds3_d5iv ->
                  case ds3_d5iv of {
                    __DEFAULT -> wild_X1c;
                    0# -> wild1_Xv
                  }
                  }
              };
            Lit ds2_d5is ->
              case ds2_d5is of { I# ds3_d5it ->
              case ds3_d5it of {
                __DEFAULT ->
                  case e_a2MX of {
                    __DEFAULT -> wild_X1c;
                    Lit ds5_d5iu ->
                      case ds5_d5iu of { I# ds6_d5iv ->
                      case ds6_d5iv of {
                        __DEFAULT -> wild_X1c;
                        0# -> wild1_Xv
                      }
                      }
                  };
                0# -> e_a2MX
              }
              }
          };
        Mul ds1_d5iw e_a2MZ ->
          join {
            fail_s6JK
            fail_s6JK _
              = join {
                  fail1_s6JM
                  fail1_s6JM _
                    = case ds1_d5iw of {
                        __DEFAULT ->
                          case e_a2MZ of {
                            __DEFAULT -> wild_X1c;
                            Lit ds4_d5iD ->
                              case ds4_d5iD of { I# ds5_d5iE ->
                              case ds5_d5iE of {
                                __DEFAULT -> wild_X1c;
                                0# -> main5
                              }
                              }
                          };
                        Lit ds4_d5iB ->
                          case ds4_d5iB of { I# ds5_d5iC ->
                          case ds5_d5iC of {
                            __DEFAULT ->
                              case e_a2MZ of {
                                __DEFAULT -> wild_X1c;
                                Lit ds7_d5iD ->
                                  case ds7_d5iD of { I# ds8_d5iE ->
                                  case ds8_d5iE of {
                                    __DEFAULT -> wild_X1c;
                                    0# -> main5
                                  }
                                  }
                              };
                            0# -> main5
                          }
                          }
                      } } in
                case e_a2MZ of {
                  __DEFAULT -> jump fail1_s6JM void#;
                  Lit ds3_d5iz ->
                    case ds3_d5iz of { I# ds4_d5iA ->
                    case ds4_d5iA of {
                      __DEFAULT -> jump fail1_s6JM void#;
                      1# -> ds1_d5iw
                    }
                    }
                } } in
          case ds1_d5iw of {
            __DEFAULT -> jump fail_s6JK void#;
            Lit ds2_d5ix ->
              case ds2_d5ix of { I# ds3_d5iy ->
              case ds3_d5iy of {
                __DEFAULT -> jump fail_s6JK void#;
                1# -> e_a2MZ
              }
              }
          };
        Neg ds1_d5iF ->
          case ds1_d5iF of {
            __DEFAULT -> wild_X1c;
            Neg e_a2N1 -> e_a2N1
          }
      }

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
main4
main4 = I# 1#

-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
main3
main3 = Lit main4

-- RHS size: {terms: 40, types: 2,087, coercions: 412, joins: 0/0}
$fGenericExpr1
$fGenericExpr1
  = \ @ x_a53m x1_a3Bq ->
      case x1_a3Bq of {
        Lit g1_a3Br -> L1 (L1 (g1_a3Br `cast` <Co:44>));
        Add g1_a3Bs g2_a3Bt ->
          L1
            (R1
               (L1
                  ((:*: (g1_a3Bs `cast` <Co:22>) (g2_a3Bt `cast` <Co:22>))
                   `cast` <Co:37>)));
        Mul g1_a3Bu g2_a3Bv ->
          L1
            (R1
               (R1
                  ((:*: (g1_a3Bu `cast` <Co:22>) (g2_a3Bv `cast` <Co:22>))
                   `cast` <Co:37>)));
        Div g1_a3Bw g2_a3Bx ->
          R1
            (L1
               ((:*: (g1_a3Bw `cast` <Co:22>) (g2_a3Bx `cast` <Co:22>))
                `cast` <Co:37>));
        Sub g1_a3By g2_a3Bz ->
          R1
            (R1
               (L1
                  ((:*: (g1_a3By `cast` <Co:22>) (g2_a3Bz `cast` <Co:22>))
                   `cast` <Co:37>)));
        Neg g1_a3BA -> R1 (R1 (R1 (g1_a3BA `cast` <Co:44>)))
      }

-- RHS size: {terms: 50, types: 1,251, coercions: 588, joins: 0/0}
$fGenericExpr_$cto
$fGenericExpr_$cto
  = \ @ x_a56O ds_d5iT ->
      case ds_d5iT `cast` <Co:202> of {
        L1 ds1_d5iV ->
          case ds1_d5iV of {
            L1 ds2_d5iW -> Lit (ds2_d5iW `cast` <Co:41>);
            R1 ds2_d5iZ ->
              case ds2_d5iZ of {
                L1 ds3_d5j0 ->
                  case ds3_d5j0 `cast` <Co:36> of { :*: ds4_d5j2 ds5_d5j3 ->
                  Add (ds4_d5j2 `cast` <Co:20>) (ds5_d5j3 `cast` <Co:20>)
                  };
                R1 ds3_d5j6 ->
                  case ds3_d5j6 `cast` <Co:36> of { :*: ds4_d5j8 ds5_d5j9 ->
                  Mul (ds4_d5j8 `cast` <Co:20>) (ds5_d5j9 `cast` <Co:20>)
                  }
              }
          };
        R1 ds1_d5jc ->
          case ds1_d5jc of {
            L1 ds2_d5jd ->
              case ds2_d5jd `cast` <Co:36> of { :*: ds3_d5jf ds4_d5jg ->
              Div (ds3_d5jf `cast` <Co:20>) (ds4_d5jg `cast` <Co:20>)
              };
            R1 ds2_d5jj ->
              case ds2_d5jj of {
                L1 ds3_d5jk ->
                  case ds3_d5jk `cast` <Co:36> of { :*: ds4_d5jm ds5_d5jn ->
                  Sub (ds4_d5jm `cast` <Co:20>) (ds5_d5jn `cast` <Co:20>)
                  };
                R1 ds3_d5jq -> Neg (ds3_d5jq `cast` <Co:41>)
              }
          }
      }

-- RHS size: {terms: 3, types: 1, coercions: 208, joins: 0/0}
$fGenericExpr
$fGenericExpr
  = C:Generic ($fGenericExpr1 `cast` <Co:208>) $fGenericExpr_$cto

Rec {
-- RHS size: {terms: 7, types: 9, coercions: 215, joins: 0/0}
$s$fGTransforma:+:_$cgtransform_$s$fTransformRecab_$ctransformRec
$s$fGTransforma:+:_$cgtransform_$s$fTransformRecab_$ctransformRec
  = \ f_a1S6 x_a1S7 ->
      $fGenericExpr_$cto
        (($s$fGTransforma:+:_$cgtransform f_a1S6 ($fGenericExpr1 x_a1S7))
         `cast` <Co:215>)

-- RHS size: {terms: 1, types: 0, coercions: 20, joins: 0/0}
$s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
$s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
  = $s$fGTransformaK10_$cgtransform_r76Y `cast` <Co:20>

-- RHS size: {terms: 76, types: 2,626, coercions: 652, joins: 0/0}
$s$fGTransforma:+:_$cgtransform
$s$fGTransforma:+:_$cgtransform
  = \ @ x1_a2vt f_a1Sn ds_d2yw ->
      case ds_d2yw of {
        L1 x2_a1So ->
          L1
            (case x2_a1So of wild1_X39 {
               L1 x4_X1UE -> wild1_X39;
               R1 y1_a1Sp ->
                 R1
                   (case y1_a1Sp of {
                      L1 x4_X1UJ ->
                        L1
                          (case x4_X1UJ `cast` <Co:38> of { :*: x5_a1Si y2_a1Sj ->
                           (:*:
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (x5_a1Si `cast` <Co:16>))
                               `cast` <Co:17>)
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (y2_a1Sj `cast` <Co:16>))
                               `cast` <Co:17>))
                           `cast` <Co:39>
                           });
                      R1 y2_X1UG ->
                        R1
                          (case y2_X1UG `cast` <Co:38> of { :*: x4_a1Si y3_a1Sj ->
                           (:*:
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (x4_a1Si `cast` <Co:16>))
                               `cast` <Co:17>)
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (y3_a1Sj `cast` <Co:16>))
                               `cast` <Co:17>))
                           `cast` <Co:39>
                           })
                    })
             });
        R1 y1_a1Sp ->
          R1
            (case y1_a1Sp of {
               L1 x2_a1So ->
                 L1
                   (case x2_a1So `cast` <Co:38> of { :*: x4_a1Si y2_a1Sj ->
                    (:*:
                       (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                           f_a1Sn (x4_a1Si `cast` <Co:16>))
                        `cast` <Co:17>)
                       (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                           f_a1Sn (y2_a1Sj `cast` <Co:16>))
                        `cast` <Co:17>))
                    `cast` <Co:39>
                    });
               R1 y2_X1UF ->
                 R1
                   (case y2_X1UF of {
                      L1 x2_a1So ->
                        L1
                          (case x2_a1So `cast` <Co:38> of { :*: x4_a1Si y3_a1Sj ->
                           (:*:
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (x4_a1Si `cast` <Co:16>))
                               `cast` <Co:17>)
                              (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                                  f_a1Sn (y3_a1Sj `cast` <Co:16>))
                               `cast` <Co:17>))
                           `cast` <Co:39>
                           });
                      R1 y3_X1UL ->
                        R1
                          (($s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
                              f_a1Sn (y3_X1UL `cast` <Co:39>))
                           `cast` <Co:41>)
                    })
             })
      }

-- RHS size: {terms: 7, types: 10, coercions: 6, joins: 0/0}
$s$fGTransformaK10_$cgtransform_r76Y
$s$fGTransformaK10_$cgtransform_r76Y
  = \ @ x_X2vo f_a1Sw ds_d2ye ->
      f_a1Sw
        ($s$fGTransforma:+:_$cgtransform_$s$fTransformRecab_$ctransformRec
           f_a1Sw (ds_d2ye `cast` <Co:6>))
end Rec }

-- RHS size: {terms: 46, types: 612, coercions: 1,133, joins: 0/0}
main7
main7
  = \ x2_a1So ->
      case x2_a1So of {
        L1 x1_X1U5 -> main_f (Lit (x1_X1U5 `cast` <Co:43>));
        R1 y1_a1Sp ->
          case y1_a1Sp of {
            L1 x1_X1Ub ->
              case x1_X1Ub `cast` <Co:39> of { :*: x3_a1Si y2_a1Sj ->
              main_f
                (Add
                   (main_f
                      ($fGenericExpr_$cto
                         (($s$fGTransforma:+:_$cgtransform
                             main_f ($fGenericExpr1 (x3_a1Si `cast` <Co:25>)))
                          `cast` <Co:228>)))
                   (main_f
                      ($fGenericExpr_$cto
                         (($s$fGTransforma:+:_$cgtransform
                             main_f ($fGenericExpr1 (y2_a1Sj `cast` <Co:25>)))
                          `cast` <Co:228>))))
              };
            R1 y2_X1Uc ->
              case y2_X1Uc `cast` <Co:39> of { :*: x1_a1Si y3_a1Sj ->
              main_f
                (Mul
                   (main_f
                      ($fGenericExpr_$cto
                         (($s$fGTransforma:+:_$cgtransform
                             main_f ($fGenericExpr1 (x1_a1Si `cast` <Co:25>)))
                          `cast` <Co:228>)))
                   (main_f
                      ($fGenericExpr_$cto
                         (($s$fGTransforma:+:_$cgtransform
                             main_f ($fGenericExpr1 (y3_a1Sj `cast` <Co:25>)))
                          `cast` <Co:228>))))
              }
          }
      }

-- RHS size: {terms: 6, types: 197, coercions: 86, joins: 0/0}
main2
main2
  = main7
      (R1
         (L1
            ((:*: (main5 `cast` <Co:24>) (main3 `cast` <Co:24>))
             `cast` <Co:38>)))

-- RHS size: {terms: 4, types: 9, coercions: 0, joins: 0/0}
main1
main1 = \ s_a5kx -> (# s_a5kx, main2 #)

-- RHS size: {terms: 1, types: 0, coercions: 3, joins: 0/0}
main
main = main1 `cast` <Co:3>

-- RHS size: {terms: 2, types: 1, coercions: 3, joins: 0/0}
main8
main8 = runMainIO1 (main1 `cast` <Co:3>)

-- RHS size: {terms: 1, types: 0, coercions: 3, joins: 0/0}
main
main = main8 `cast` <Co:3>


------ Local rules for imported ids --------
"SPEC/Main $fGTransformaK10_$cgtransform @ Expr"
    forall $dTransformRec_s6JW.
      $fGTransformaK10_$cgtransform $dTransformRec_s6JW
      = $s$fGTransforma:+:_$cgtransform_$s$fGTransformaK10_$cgtransform
"SPEC/Main $fTransformRecab_$ctransformRec @ Expr @ Expr"
    forall $dGTransform_s6JZ $dGeneric_s6JY.
      $fTransformRecab_$ctransformRec $dGeneric_s6JY $dGTransform_s6JZ
      = $s$fGTransforma:+:_$cgtransform_$s$fTransformRecab_$ctransformRec
"SPEC/Main $fGTransforma:+:_$cgtransform @ Expr @ (C1
                                                    ('MetaCons "Lit" 'PrefixI 'False)
                                                    (S1
                                                       ('MetaSel
                                                          'Nothing
                                                          'NoSourceUnpackedness
                                                          'NoSourceStrictness
                                                          'DecidedLazy)
                                                       (Rec0 Int))
                                                  :+: (C1
                                                         ('MetaCons "Add" 'PrefixI 'False)
                                                         (S1
                                                            ('MetaSel
                                                               'Nothing
                                                               'NoSourceUnpackedness
                                                               'NoSourceStrictness
                                                               'DecidedLazy)
                                                            (Rec0 Expr)
                                                          :*: S1
                                                                ('MetaSel
                                                                   'Nothing
                                                                   'NoSourceUnpackedness
                                                                   'NoSourceStrictness
                                                                   'DecidedLazy)
                                                                (Rec0 Expr))
                                                       :+: C1
                                                             ('MetaCons "Mul" 'PrefixI 'False)
                                                             (S1
                                                                ('MetaSel
                                                                   'Nothing
                                                                   'NoSourceUnpackedness
                                                                   'NoSourceStrictness
                                                                   'DecidedLazy)
                                                                (Rec0 Expr)
                                                              :*: S1
                                                                    ('MetaSel
                                                                       'Nothing
                                                                       'NoSourceUnpackedness
                                                                       'NoSourceStrictness
                                                                       'DecidedLazy)
                                                                    (Rec0 Expr)))) @ (C1
                                                                                        ('MetaCons
                                                                                           "Div"
                                                                                           'PrefixI
                                                                                           'False)
                                                                                        (S1
                                                                                           ('MetaSel
                                                                                              'Nothing
                                                                                              'NoSourceUnpackedness
                                                                                              'NoSourceStrictness
                                                                                              'DecidedLazy)
                                                                                           (Rec0
                                                                                              Expr)
                                                                                         :*: S1
                                                                                               ('MetaSel
                                                                                                  'Nothing
                                                                                                  'NoSourceUnpackedness
                                                                                                  'NoSourceStrictness
                                                                                                  'DecidedLazy)
                                                                                               (Rec0
                                                                                                  Expr))
                                                                                      :+: (C1
                                                                                             ('MetaCons
                                                                                                "Sub"
                                                                                                'PrefixI
                                                                                                'False)
                                                                                             (S1
                                                                                                ('MetaSel
                                                                                                   'Nothing
                                                                                                   'NoSourceUnpackedness
                                                                                                   'NoSourceStrictness
                                                                                                   'DecidedLazy)
                                                                                                (Rec0
                                                                                                   Expr)
                                                                                              :*: S1
                                                                                                    ('MetaSel
                                                                                                       'Nothing
                                                                                                       'NoSourceUnpackedness
                                                                                                       'NoSourceStrictness
                                                                                                       'DecidedLazy)
                                                                                                    (Rec0
                                                                                                       Expr))
                                                                                           :+: C1
                                                                                                 ('MetaCons
                                                                                                    "Neg"
                                                                                                    'PrefixI
                                                                                                    'False)
                                                                                                 (S1
                                                                                                    ('MetaSel
                                                                                                       'Nothing
                                                                                                       'NoSourceUnpackedness
                                                                                                       'NoSourceStrictness
                                                                                                       'DecidedLazy)
                                                                                                    (Rec0
                                                                                                       Expr))))"
    forall $dGTransform1_s6K2 $dGTransform_s6K1.
      $fGTransforma:+:_$cgtransform $dGTransform_s6K1 $dGTransform1_s6K2
      = $s$fGTransforma:+:_$cgtransform


Linking Plate ...

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment