hmt-base-0.20: Haskell Music Theory Base
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Read

Description

Read functions.

Synopsis

Documentation

reads_to_read_precise :: ReadS t -> String -> Maybe t Source #

Transform ReadS function into precise Read function. Requires using all the input to produce a single token. The only exception is a singular trailing white space character.

read_maybe :: Read a => String -> Maybe a Source #

reads_to_read_precise of reads.

read_maybe "1.0" :: Maybe Int
read_maybe "1.0" :: Maybe Float

read_def :: Read a => a -> String -> a Source #

Variant of read_maybe with default value.

map (read_def 0) ["2","2:","2\n"] == [2,0,2]

read_err_msg :: Read a => String -> String -> a Source #

Variant of read_maybe that errors on Nothing, printing message.

read_err :: Read a => String -> a Source #

Default message.

reads_exact :: Read a => String -> Maybe a Source #

Variant of reads requiring exact match, no trailing white space.

map reads_exact ["1.5","2,5"] == [Just 1.5,Nothing]

reads_exact_err :: Read a => String -> String -> a Source #

Variant of reads_exact that errors on failure.

Type specific variants

read_integral_allow_commas_maybe :: Read i => String -> Maybe i Source #

Allow commas as thousand separators.

let r = [Just 123456,Just 123456,Nothing,Just 123456789]
map read_integral_allow_commas_maybe ["123456","123,456","1234,56","123,456,789"] == r

read_int_allow_commas :: String -> Int Source #

Type specialised.

map read_int_allow_commas ["123456","123,456","123,456,789"] == [123456,123456,123456789]

read_ratio_with_div_err :: (Integral i, Read i) => String -> Ratio i Source #

Read a ratio where the division is given by / instead of % and the integers allow commas.

map read_ratio_with_div_err ["123,456/7","123,456,789"] == [123456/7,123456789]

read_ratio_allow_commas_err :: (Integral i, Read i) => String -> String -> Ratio i Source #

Read Ratio, allow commas for thousand separators.

read_ratio_allow_commas_err "327,680" "177,147" == 327680 / 177147

delete_trailing_point :: String -> String Source #

Delete trailing ., read fails for 700..

read_fractional_allow_trailing_point_err :: Read n => String -> n Source #

read_err disallows trailing decimal points.

map read_fractional_allow_trailing_point_err ["123.","123.4"] == [123.0,123.4]

Plain type specialisations

read_maybe_int :: String -> Maybe Int Source #

Type specialised read_maybe.

map read_maybe_int ["2","2:","2\n","x"] == [Just 2,Nothing,Just 2,Nothing]

read_int :: String -> Int Source #

Type specialised read_err.

read_double :: String -> Double Source #

Type specialised read_err.

read_maybe_rational :: String -> Maybe Rational Source #

Type specialised read_maybe.

map read_maybe_rational ["1","1%2","1/2"] == [Nothing,Just (1/2),Nothing]

read_rational :: String -> Rational Source #

Type specialised read_err.

read_rational "1%4"

Numeric variants

read_bin :: Integral a => String -> Maybe a Source #

Read binary integer.

mapMaybe read_bin (words "000 001 010 011 100 101 110 111") == [0 .. 7]

read_bin_err :: Integral a => String -> a Source #

Erroring variant.

HEX

read_hex_err :: (Eq n, Integral n) => String -> n Source #

Error variant of readHex.

read_hex_err "F0B0" == 61616

read_hex_sz :: (Eq n, Integral n) => Int -> String -> n Source #

Read hex value from string of at most k places.

read_hex_word32 :: String -> Word32 Source #

Read hexadecimal representation of 32-bit unsigned word.

map read_hex_word32 ["00000000","12345678","FFFFFFFF"] == [minBound,305419896,maxBound]

Rational

rational_parse :: (Read t, Integral t) => String -> Ratio t Source #

Parser for rational_pp.

map rational_parse ["1","3/2","5/4","2"] == [1,3/2,5/4,2]
rational_parse "" == undefined