[Haskell-cafe] Proposal: Non-recursive let

Evan Laforge qdunkan at gmail.com
Sat Jul 20 21:36:33 CEST 2013


On Tue, Jul 16, 2013 at 5:20 PM, Richard A. O'Keefe <ok at cs.otago.ac.nz> wrote:
> Brian Marick sent me a couple of his stickers.
> The one I have on my door reads "to be less wrong than yesterday".
> The other one I keep free to bring out and wave around:
>
>         "An example would be handy about now."

Just by coincidence, I recently wrote this:

midi_to_pitch :: TheoryFormat.Format -> Maybe Pitch.Key
    -> Pitch.NoteNumber -> Maybe Theory.Pitch
midi_to_pitch fmt key nn =
    either (const Nothing) Just $
        TheoryFormat.fmt_to_absolute fmt key pitch
    where
    -- TODO if I support frac I can use this for twelve too
    (semis, _frac) = properFraction (Pitch.nn_to_double nn)
    Theory.Pitch oct (Theory.Note pc accs) =
        Theory.semis_to_pitch_sharps TheoryFormat.piano_layout
            (Theory.nn_to_semis semis)
    (oct1, pc1) = adjust_octave (TheoryFormat.fmt_pc_per_octave fmt) 7 oct pc
    pitch = Theory.Pitch oct1 (Theory.Note pc1 accs)

kbd_to_pitch :: Theory.PitchClass -> Pitch.Octave -> Theory.PitchClass
    -> Theory.Accidentals -> Theory.Pitch
kbd_to_pitch pc_per_octave oct pc accidentals =
    Theory.Pitch (add_oct + oct1) (Theory.Note pc2 accidentals)
    where
    (oct1, pc1) = adjust_octave pc_per_octave 10 oct pc
    -- If the scale is shorter than the kbd, go up to the next octave on the
    -- same row.
    (add_oct, pc2) = pc1 `divMod` pc_per_octave

adjust_octave :: Theory.PitchClass -> Theory.PitchClass -> Pitch.Octave
    -> Theory.PitchClass -> (Pitch.Octave, Theory.PitchClass)
adjust_octave pc_per_octave kbd_per_octave oct pc = (oct2, pc2)
    where
    rows = ceiling $ fromIntegral pc_per_octave / fromIntegral kbd_per_octave
    (oct2, offset) = oct `divMod` rows
    pc2 = offset * kbd_per_octave + pc


Also, fragments like this are fairly common:

        Right pitch_ ->
            let pitch = pitch_
                    { Theory.pitch_note = (Theory.pitch_note pitch_)
                        { Theory.note_accidentals = 0 }
                    }
                accs = Theory.pitch_accidentals pitch_
            in Just $ ScaleDegree.scale_degree_just
                (smap_named_intervals smap)
                (smap_accidental_interval smap ^^ accs)
                (pitch_nn smap pitch) (pitch_note fmt pitch)

My convention is when I have a a series of transformations that have
to be named for whatever reason, I suffix with numbers.  When I have a
function argument (or case-bound variable as in this case) that has to
be "cooked" before it can be used, I suffix it with _.  That way code
inside the function is not likely to accidentally use the un-cooked
version (this has happened when I left the uncooked version normal and
suffixed the cooked version with a 1 or something).  In monadic style,
I use 'x <- return $ f x' a fair amount.

I'm just sending this to point out that it actually is a real issue.
And on the odd chance that someone wants to tell me that I'm doing it
wrong and here's a better idea :)  I'm not about to import Monad.State
and wrap the whole expression in a state call just to replace one or
two variables, both the syntactic overhead and the "conversion"
overhead make it not worth it.

However, I'm also not agitating for a non-recursive let, I think that
ship has sailed.  Besides, if it were added people would start
wondering about non-recursive where, and it would introduce an
exception to haskell's pretty consistently order-independent
declaration style.




More information about the Haskell-Cafe mailing list