Computing the multiplication table of a group using the GHC inliner ; )

Hello, turns out that you can define the group operation of the symmetric group on 3 elements in this abstract way (via the isomorphism to the group of bijective functions from a three-element type to itself): s3mult g2 g1 = fromFun (toFun g2 . toFun g1) and convince GHC to compile it down to a nested case statement. It even somehow made the left multiplication with the identity non-strict. Just thought it's neat ;) $ ghc-core S3.hs -funfolding-use-threshold=64 ... -- identifiers manually un-qualified for readability s3mult = \ (g2_ahA :: S3) (g1_ahB :: S3) -> case g2_ahA of _ { S3abc -> g1_ahB; S3bca -> case g1_ahB of _ { S3abc -> S3bca; S3bca -> S3cab; S3cab -> S3abc; S3acb -> S3bac; S3bac -> S3cba; S3cba -> S3acb }; S3cab -> case g1_ahB of _ { S3abc -> S3cab; S3bca -> S3abc; S3cab -> S3bca; S3acb -> S3cba; S3bac -> S3acb; S3cba -> S3bac }; S3acb -> case g1_ahB of _ { S3abc -> S3acb; S3bca -> S3cba; S3cab -> S3bac; S3acb -> S3abc; S3bac -> S3cab; S3cba -> S3bca }; S3bac -> case g1_ahB of _ { S3abc -> S3bac; S3bca -> S3acb; S3cab -> S3cba; S3acb -> S3bca; S3bac -> S3abc; S3cba -> S3cab }; S3cba -> case g1_ahB of _ { S3abc -> S3cba; S3bca -> S3bac; S3cab -> S3acb; S3acb -> S3cab; S3bac -> S3bca; S3cba -> S3abc } } -- inverse s3inv = \ (g_ahC :: S3) -> case g_ahC of _ { S3abc -> S3abc; S3bca -> S3cab; S3cab -> S3bca; S3acb -> S3acb; S3bac -> S3bac; S3cba -> S3cba } --- end core --- --- source --- module S3 where -- | Symmetric group / permutation group on 3 elements data S3 = S3abc | S3bca | S3cab | S3acb | S3bac | S3cba deriving(Eq) -- | Returns an element of S3 satisfying the given predicate s3the :: (S3 -> Bool) -> S3 s3the p | p S3abc = S3abc | p S3acb = S3acb | p S3bac = S3bac | p S3bca = S3bca | p S3cba = S3cba | p S3cab = S3cab | otherwise = error "s3the: no element satisfies the predicate" data ABC = A | B | C deriving(Eq) toFun :: S3 -> ABC -> ABC toFun g = case g of S3abc -> mkFun A B C S3bca -> mkFun B C A S3cab -> mkFun C A B S3acb -> mkFun A C B S3bac -> mkFun B A C S3cba -> mkFun C B A where mkFun imA _ _ A = imA mkFun _ imB _ B = imB mkFun _ _ imC _ = imC fromFun :: (ABC -> ABC) -> S3 fromFun f = s3the (\g -> toFun g A == f A && toFun g B == f B) s3mult :: S3 -> S3 -> S3 s3mult g2 g1 = fromFun (toFun g2 . toFun g1) s3inv g = s3the (\g' -> s3mult g' g == S3abc)

2011/3/22 Daniel Schüssler
Hello,
turns out that you can define the group operation of the symmetric group on 3 elements in this abstract way (via the isomorphism to the group of bijective functions from a three-element type to itself):
s3mult g2 g1 = fromFun (toFun g2 . toFun g1)
and convince GHC to compile it down to a nested case statement. It even somehow made the left multiplication with the identity non-strict. Just thought it's neat ;)
That's quite fantastic. Antoine
participants (2)
-
Antoine Latter
-
Daniel Schüssler