
On Tue, Nov 28, 2023 at 07:54:52AM -0800, Todd Wilson wrote:
I mentioned earlier wanting to avoid modules for this, and hoping for something like the SML syntax that Richard mentioned, even making my own equivalent syntactic proposal
{f = ...; g = ...} where h = ...
which looks in line with current Haskell conventions. Given the existing options, however, I would probably go with a top-level pair definition:
(f,g) = (..., ...) where h = ...
or
(f,g) = let f' = ...; g' = ...' ; h = ... in (f',g')
as mentioned by Jeff. Thanks to all who contributed!
Or, with heavy artilery, that I rather expect entirely optimises away: {-# LANGUAGE DataKinds, GADTs, LambdaCase, StandaloneKindSignatures, TypeFamilies #-} module Demo(f, g) where import Data.Kind (Type) type FG :: Bool -> Type type family FG b where FG False = String -> Bool FG True = Int -> String data SBool b where SFalse :: SBool False STrue :: SBool True f :: String -> Bool f = fg SFalse g :: Int -> String g = fg STrue fg :: SBool b -> FG b fg = \ case SFalse -> f' STrue -> g' where h :: Int -> String h = show f' s = s == h 0 g' i = h (i + 1) {-# INLINE fg #-} The "Core" output shows: -- RHS size: {terms: 15, types: 14, coercions: 0, joins: 0/0} g :: Int -> String g = \ (i :: Int) -> case i of { I# x -> case $wshowSignedInt 0# (+# x 1#) [] of { (# ww5, ww6 #) -> : ww5 ww6 } } -- RHS size: {terms: 9, types: 11, coercions: 0, joins: 0/0} f1 :: String f1 = case $wshowSignedInt 0# 0# [] of { (# ww5, ww6 #) -> : ww5 ww6 } -- RHS size: {terms: 4, types: 1, coercions: 0, joins: 0/0} f :: String -> Bool f = \ (s :: String) -> eqString s f1 -- Viktor.