Skip to content

Instantly share code, notes, and snippets.

@shapr
Created February 9, 2023 18:02
Show Gist options
  • Save shapr/c454789916eb7320c94fb810d19314ce to your computer and use it in GitHub Desktop.
Save shapr/c454789916eb7320c94fb810d19314ce to your computer and use it in GitHub Desktop.
transcode all FLAC files to 16bit 44.1 kHz with sox
module Main where
import Core
import System.Directory
import System.FilePath
import System.Process
import Data.Maybe
import Data.List
main :: IO ()
main = do
let allDirs = ("/home/shae/Music" </> ) <$> dirList
print allDirs
eachFoo <- mapM listDirectory' allDirs
let flacsOnly = filter (("calf" ==) . take 4 . reverse) <$> eachFoo
singles = filter ((1 ==) . length) flacsOnly
flacsOnly' = filter ((1 <) . length) flacsOnly
transCode = concatMap (fmap transcodeCommand) (newNames <$> flacsOnly')
print $ "singles are " <> show singles
mapM_ callCommand transCode
wrapFile :: FilePath -> FilePath
wrapFile f = "\"" <> f <> "\""
transcodeCommand :: (String, String) -> String
transcodeCommand (old,new) =
mconcat [", sox --show-progress --no-clobber "
, wrapFile old
, " -r 44100 -b 16 "
, wrapFile $ replaceFileName old new
]
listDirectory' :: FilePath -> IO [FilePath]
listDirectory' dir = do
fs <- listDirectory dir
pure $ (dir </>) <$> fs
prefexes :: [[Char]]
prefexes = [[a,b,'-'] | a <- letrs, b <- letrs]
where letrs = ['A' .. 'Z']
newNames :: [FilePath] -> [(FilePath,FilePath)]
newNames oops@[_] = error $ "newNames breaks with one input " <> show oops
newNames paths = zip (sort paths) $ zipWith (<>) prefexes newPaths
where cp = commonPrefix paths :: FilePath
newPaths = sort $ drop (length cp) <$> paths
the :: Eq a => [a] -> Maybe a
the [] = Nothing
the (x:xs)
| all (==x) xs = Just x
| otherwise = Nothing
commonPrefix :: Eq a => [[a]] -> [a]
commonPrefix = catMaybes . takeWhile isJust . map the . transpose
commonPref (a:as) (b:bs) theSame =
if a == b
then commonPref as bs (theSame <> a)
else theSame
data MyMaybe a where
MyJust :: a -> MyMaybe a
MyNothing :: MyMaybe a
{-
input is a list of directory names
1. get a list of all the *.flac files in that directory
2. find the longest common prefix
replace that with 'A' .. 'Z' in order for the output name
3. call ", sox --show-progress --no-clobber " inputFile " -r 44100 -b 16 " thisLetter outputFile
(- 127 66)
-}
dirList :: [FilePath]
dirList = [ -- "beats_antique/2010_Dia_de_los_Muertos"
-- , "beats_antique/2012_Mayans_vs_Aliens"
-- , "beats_antique/2019_Bhangra_Saanj" -- has only one file!
-- "beats_antique/2019_The_Grand_Bizarre"
-- "beats_antique/2021_Singles"
-- , "chinese_man/2015_Sho-Bro"
-- , "chinese_man/2017_Shikantaza"
-- , "chinese_man/2018_Shikantaza_Remix"
-- , "danger/2014_July-2013"
-- , "danger/2017_drum"
-- , "danger/2019_origins"
-- , "danheim/2018_runagaldr"
-- , "danheim/2021_domadagr"
-- , "danheim/singles"
-- , "dead-end/2019-pure-vanilla"
-- , "draper/2018_Paro"
-- , "draper/2019_Kudoclasm"
-- , "einar_selvik/2017_snake_pit_poetry"
-- , "einar_selvik/2020_assassins_creed"
-- , "evian_christ/2014_Waterfall"
-- , "glitch_mob/2017_the_clouds_breathe_for_you"
-- "glitch_mob/2018_see_without_eyes"
-- , "glitch_mob/2018_see_without_eyes_deluxe"
-- , "glitch_mob/2019_singles"
-- , "glitch_mob/2020_chemicals"
-- , "godspeed_you_black_emperor/1993_all_lights_fucked_on_the_hairy_amp_drooling"
-- , "godspeed_you_black_emperor/2017_luciferian_towers"
-- , "heilung/2018_Lifa"
-- , "hudson_mohawke/2015_lantern"
-- , "hudson_mohawke/2020_black_cherry" -- ONE FILE
"kraddy/2009_Freakshow"
, "kraddy/2011_Anthems_of_the_Hero"
, "oliver_coates/2020_skins_n_slime"
, "onhell/2020_grime_beats_vol_1"
, "onhell/2022_grime_beats_vol_2"
, "outer_wilds/2022-outer-wilds-deluxe"
, "pantyraid/2016_AfterGlow"
-- "pine_hill_haints/2020_13"
, "proleter/2012_curses-from-past-times-bonus"
, "proleter/2014_tribute-to-the-mastkers-vol-1"
, "proleter/2015_tribute-to-the-mastkers-vol-2"
, "proleter/2017_life-playing-tricks"
, "proleter/2018_curses_from_past_times"
, "rachika_nayar/2022_heaven_come_crashing"
, "sleigh_bells/2021_texis"
, "super_onze/2016_jo_kanga_djiribi"
, "super_onze/2020-yehia-samak-ngoni-by-night"
, "the_modern_savage/2015_unfazed"
, "tipper/2019_jettison_mind_hatch"
, "tipper/2021_insolito"
, "tipper/2022_marble_hunting"
, "too_many_zooz/2014_09_fanimals"
, "too_many_zooz/2014_11_brasshouse_volume_1"
, "too_many_zooz/2015_the_internet"
, "too_many_zooz/2016_subway_gawdz"
, "too_many_zooz/2018_very_too_many_zooz_xmas"
, "too_many_zooz/2019_zombiEP"
, "too_many_zooz/singles"
, "williamson/2016_backesto_park"
, "wintergatan/2017_21_instruments"
, "wintergatan/2020_wintergatan_singles"
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment