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

Music.Theory.Time.Notation

Description

Ordinary time and duration notations. In terms of Weeks, Days, Hours, Minutes, Second and Centiseconds. c.f. Music.Theory.Time.Duration.

Synopsis

Integral types

type Week = Int Source #

Week, one-indexed, ie. 1-52

type Day = Int Source #

Week, one-indexed, ie. 1-31

type Hour = Int Source #

Hour, zero-indexed, ie. 0-23

type Min = Int Source #

Minute, zero-indexed, ie. 0-59

type Sec = Int Source #

Second, zero-indexed, ie. 0-59

type Csec = Int Source #

Centi-seconds, zero-indexed, ie. 0-99

Composite types

type MinSec = (Min, Sec) Source #

Minutes, seconds as (min,sec)

type GMinSec n = (n, n) Source #

Generic MinSec

type MinCsec = (Min, Sec, Csec) Source #

Minutes, seconds, centi-seconds as (min,sec,csec)

type GMinCsec n = (n, n, n) Source #

Generic MinCsec

type Hms = (Hour, Min, Sec) Source #

(Hours,Minutes,Seconds)

type Dhms = (Day, Hour, Min, Sec) Source #

(Days,Hours,Minutes,Seconds)

Fractional types

type FDay = Double Source #

Fractional days.

type FHour = Double Source #

Fractional hour, ie. 1.50 is one and a half hours, ie. 1 hour and 30 minutes.

type FMin = Double Source #

Fractional minute, ie. 1.50 is one and a half minutes, ie. 1 minute and 30 seconds, cf. FMinSec

type FSec = Double Source #

Fractional seconds.

type FMinSec = Double Source #

Fractional minutes and seconds (mm.ss, ie. 01.45 is 1 minute and 45 seconds).

Time.UTCTime format strings.

Iso-8601

parse_iso8601_date :: String -> UTCTime Source #

Parse date in ISO-8601 extended (YYYY-MM-DD) or basic (YYYYMMDD) form.

Time.toGregorian (Time.utctDay (parse_iso8601_date "2011-10-09")) == (2011,10,09)
Time.toGregorian (Time.utctDay (parse_iso8601_date "20190803")) == (2019,08,03)

format_iso8601_date :: FormatTime t => Bool -> t -> String Source #

Format date in ISO-8601 form.

format_iso8601_date True (parse_iso8601_date "2011-10-09") == "2011-10-09"
format_iso8601_date False (parse_iso8601_date "20190803") == "20190803"

format_iso8601_week :: FormatTime t => t -> String Source #

Format date in ISO-8601 (YYYY-WWW) form.

r = ["2016-W52","2011-W40"]
map (format_iso8601_week . parse_iso8601_date) ["2017-01-01","2011-10-09"] == r

parse_iso8601_time :: String -> UTCTime Source #

Parse ISO-8601 time is extended (HH:MM:SS) or basic (HHMMSS) form.

format_iso8601_time True (parse_iso8601_time "21:44:00") == "21:44:00"
format_iso8601_time False (parse_iso8601_time "172511") == "172511"

format_iso8601_time :: FormatTime t => Bool -> t -> String Source #

Format time in ISO-8601 form.

format_iso8601_time True (parse_iso8601_date_time "2011-10-09T21:44:00") == "21:44:00"
format_iso8601_time False (parse_iso8601_date_time "20190803T172511") == "172511"

parse_iso8601_date_time :: String -> UTCTime Source #

Parse date and time in extended or basic forms.

Time.utctDayTime (parse_iso8601_date_time "2011-10-09T21:44:00") == Time.secondsToDiffTime 78240
Time.utctDayTime (parse_iso8601_date_time "20190803T172511") == Time.secondsToDiffTime 62711

format_iso8601_date_time :: FormatTime t => Bool -> t -> String Source #

Format date in YYYY-MM-DD and time in HH:MM:SS forms.

t = parse_iso8601_date_time "2011-10-09T21:44:00"
format_iso8601_date_time True t == "2011-10-09T21:44:00"
format_iso8601_date_time False t == "20111009T214400"

FMin

fmin_to_minsec :: FMin -> MinSec Source #

fsec_to_minsec . * 60

fmin_to_minsec 6.48 == (6,29)

FSec

fsec_to_picoseconds :: FSec -> Integer Source #

Translate fractional seconds to picoseconds.

fsec_to_picoseconds 78240.05

FMinSec

fminsec_to_fsec :: FMinSec -> FSec Source #

Translate fractional minutes.seconds to picoseconds.

map fminsec_to_fsec [0.45,15.355] == [45,935.5]

fminsec_to_sec :: FMinSec -> Sec Source #

Fractional minutes are mm.ss, so that 15.35 is 15 minutes and 35 seconds.

map fminsec_to_sec [0.45,15.35] == [45,935]

FHour

ffloor :: Double -> Double Source #

Type specialised fromInteger of floor.

fhour_to_hms :: FHour -> Hms Source #

Fractional hour to (hours,minutes,seconds).

fhour_to_hms 21.75 == (21,45,0)

hms_to_fhour :: Hms -> FHour Source #

Hms to fractional hours.

hms_to_fhour (21,45,0) == 21.75

fhour_to_fsec :: FHour -> FSec Source #

Fractional hour to seconds.

fhour_to_fsec 21.75 == 78300.0

FDay

utctime_to_fday :: UTCTime -> FDay Source #

Time in fractional days.

round (utctime_to_fday (parse_iso8601_date_time "2011-10-09T09:00:00")) == 55843
round (utctime_to_fday (parse_iso8601_date_time "2011-10-09T21:00:00")) == 55844

DiffTime

difftime_to_fsec :: DiffTime -> FSec Source #

DiffTime in fractional seconds.

difftime_to_fsec (hms_to_difftime (21,44,30)) == 78270

difftime_to_fmin :: DiffTime -> Double Source #

DiffTime in fractional minutes.

difftime_to_fmin (hms_to_difftime (21,44,30)) == 1304.5

difftime_to_fhour :: DiffTime -> FHour Source #

DiffTime in fractional hours.

difftime_to_fhour (hms_to_difftime (21,45,00)) == 21.75

Hms

sec_to_hms :: Sec -> Hms Source #

Seconds to (hours,minutes,seconds).

map sec_to_hms [60-1,60+1,60*60-1,60*60+1] == [(0,0,59),(0,1,1),(0,59,59),(1,0,1)]

hms_pp :: Bool -> Hms -> String Source #

Hms pretty printer.

map (hms_pp True) [(0,1,2),(1,2,3)] == ["01:02","01:02:03"]

Hms parser.

MinSec

sec_to_minsec :: Integral n => n -> GMinSec n Source #

divMod by 60.

sec_to_minsec 123 == (2,3)

minsec_to_sec :: Num n => GMinSec n -> n Source #

Inverse of sec_minsec.

minsec_to_sec (2,3) == 123

minsec_binop :: Integral t => (t -> t -> t) -> GMinSec t -> GMinSec t -> GMinSec t Source #

Convert p and q to seconds, apply f, and convert back to MinSec.

minsec_sub :: Integral n => GMinSec n -> GMinSec n -> GMinSec n Source #

minsec_binop -, assumes q precedes p.

minsec_sub (2,35) (1,59) == (0,36)

minsec_diff :: Integral n => GMinSec n -> GMinSec n -> GMinSec n Source #

minsec_binop subtract, assumes p precedes q.

minsec_diff (1,59) (2,35) == (0,36)

minsec_add :: Integral n => GMinSec n -> GMinSec n -> GMinSec n Source #

minsec_binop +.

minsec_add (1,59) (2,35) == (4,34)

minsec_sum :: Integral n => [GMinSec n] -> GMinSec n Source #

foldl of minsec_add

minsec_sum [(1,59),(2,35),(4,34)] == (9,08)

fsec_to_minsec :: FSec -> MinSec Source #

round fractional seconds to (min,sec).

map fsec_to_minsec [59.49,60,60.51] == [(0,59),(1,0),(1,1)]

minsec_pp :: MinSec -> String Source #

MinSec pretty printer.

map (minsec_pp . fsec_to_minsec) [59,61] == ["00:59","01:01"]

MinSec parser.

MinCsec

fsec_to_mincsec :: FSec -> MinCsec Source #

Fractional seconds to (min,sec,csec), csec value is rounded.

map fsec_to_mincsec [1,1.5,4/3] == [(0,1,0),(0,1,50),(0,1,33)]

mincsec_to_fsec :: Real n => GMinCsec n -> FSec Source #

Inverse of fsec_mincsec.

csec_to_mincsec :: Integral n => n -> GMinCsec n Source #

Centi-seconds to MinCsec.

map csec_to_mincsec [123,12345] == [(0,1,23),(2,3,45)]

mincsec_pp_opt :: Bool -> MinCsec -> String Source #

MinCsec pretty printer, concise mode omits centiseconds when zero.

map (mincsec_pp_opt True . fsec_to_mincsec) [1,60.5] == ["00:01","01:00.50"]

mincsec_pp :: MinCsec -> String Source #

MinCsec pretty printer.

let r = ["00:01.00","00:06.67","02:03.45"]
map (mincsec_pp . fsec_to_mincsec) [1,6+2/3,123.45] == r

mincsec_binop :: Integral t => (t -> t -> t) -> GMinCsec t -> GMinCsec t -> GMinCsec t Source #

DHms

sec_to_dhms_generic :: Integral n => n -> (n, n, n, n) Source #

Convert seconds into (days,hours,minutes,seconds).

sec_to_dhms :: Sec -> Dhms Source #

Type specialised sec_to_dhms_generic.

sec_to_dhms 1475469 == (17,1,51,9)

dhms_to_sec :: Num n => (n, n, n, n) -> n Source #

Inverse of seconds_to_dhms.

dhms_to_sec (17,1,51,9) == 1475469

parse_dhms_generic :: (Integral n, Read n) => String -> (n, n, n, n) Source #

Generic form of parse_dhms.

parse_dhms :: String -> Dhms Source #

Parse DHms text. All parts are optional, order is not significant, multiple entries are allowed.

parse_dhms "17d1h51m9s" == (17,1,51,9)
parse_dhms "1s3d" == (3,0,0,1)
parse_dhms "1h1h" == (0,2,0,0)

Week

time_to_week :: UTCTime -> Week Source #

Week that t lies in.

map (time_to_week . parse_iso8601_date) ["2017-01-01","2011-10-09"] == [52,40]

Util

span_pp :: (t -> String) -> (t, t) -> String Source #

Given printer, pretty print time span.