提出 #58484229


ソースコード 拡げる

-- {{{ Imports and Language Extensions
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE CPP, TemplateHaskell #-}
{-# HLINT ignore "Unused LANGUAGE pragma" #-}
{-# OPTIONS_GHC -Wno-unused-imports -Wno-unused-top-binds -Wno-dodgy-imports -Wno-orphans -Wno-unrecognised-pragmas #-}

import Control.Applicative
import Control.Exception
import Control.Monad
import Control.Monad.Primitive (PrimMonad, PrimState)
import Control.Monad.ST
import Control.Monad.State
import Data.Array.Base (IArray (numElements))
import Data.Array.IArray
import Data.Array.IO
import Data.Array.MArray
import Data.Array.ST
import Data.Array.Unboxed (UArray)
import Data.Bifunctor
import Data.Bits
import Data.Bool
import Data.ByteString.Char8 qualified as BS
import Data.ByteString.Lazy.Char8 qualified as BSL
import Data.Char
import Data.Coerce (coerce)
import Data.Foldable
import Data.Function
import Data.HashMap.Strict qualified as HM
import Data.HashPSQ qualified as HashPSQ
import Data.HashSet qualified as HS
import Data.Hashable qualified as Hashable
import Data.Heap qualified as Heap
import Data.IORef
import Data.IntMap.Strict qualified as IM
import Data.IntPSQ qualified as IntPSQ
import Data.IntSet qualified as IS
import Data.List
import Data.List.Extra hiding ((!?))
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.Ord hiding (clamp)
import Data.STRef
import Data.Sequence (Seq (Empty, (:<|), (:|>)), (<|), (|>))
import Data.Sequence qualified as Seq
import Data.Set qualified as Set
import Data.Text qualified as Text
import Data.Text.IO qualified as TIO
import Data.Traversable
import Data.Tuple
import Data.Tuple.Extra (first3, fst3, second3, snd3, thd3, third3)
import Data.Vector qualified as V
import Data.Vector.Algorithms.Intro qualified as VAI
import Data.Vector.Generic qualified as VG
import Data.Vector.Unboxed qualified as VU
import Data.Vector.Unboxed.Mutable qualified as VUM
import Debug.Trace (traceShow)
import GHC.IO (unsafePerformIO)
import System.Environment (lookupEnv)
import System.Exit (exitSuccess)
import System.IO (hFlush, stdout)
-- }}}

-- solve edges s t order = go 0 0 (fst (edges !! 0)) s  -- 初期地点は (fst (edges !! 0))
--   where
--     go !acc !idx (!x, !y) !weight
--       | idx == length edges = acc  -- 全ての辺を辿り終えたら終了
--       | otherwise =
--         let ((a, b), (c, d)) = edges !! (order !! idx - 1)  -- 順番に従って辺を取得
--             weight' = if (order !! idx) `elem` order then t else s
--             acc' = acc + weight' * (abs (x - a) + abs (y - b))
--         in go acc' (idx + 1) (c, d) weight'

-- solve edges s t order = 
--   where 
--     go !acc !idx (!x, !y) !isOnEdge
--       | idx == length edges = acc  -- 全ての辺を辿り終えたら終了
--       | otherwise =
--         let ((a, b), (c, d)) = edges !! (order !! idx - 1)  -- 順番に従って辺を取得

--         -- isOnEdgeがTrueの時 (つまり、x==aかつy==bの時)
--         -- 重さはt
--         -- (x,y)から(c,d)に移動する
--         let distance = sqrt ((x - c)^2 + (y - d)^2)
--         let time = t * distance
--         let acc' = acc + time
--         go acc' (idx + 1) (c, d) False
--         -- isOnEdgeがFalseの時 (つまり、x!=aかつy!=bの時)
--         -- 重さはs
--         -- (x,y)から(a,b)に移動する
--         let distance = sqrt ((x - a)^2 + (y - b)^2)
--         let time = s * distance
--         let acc' = acc + time
--         go acc' (idx + 1) (a, b) True

-- main = do 
--   [n, s, t] <- getInts
--   info <- replicateM n getInts
--   -- info::[[Int]]をedges::[((Int,Int),(Int,Int))]に変換
--   let edges = map (\[a,b,c,d] -> ((a,b),(c,d))) info
--   -- print edges
  
--   -- どの順番で辺を巡るかを全探索
--   -- 辺のどちらに向かうかで2通り
--   -- 辺の上でない時の重さはs、辺の上の時の重さはtで計算する
--   let ans = minimum [solve edges s t order | order <- permutations [1..n]]

--   print ans

-- solve :: [((Int, Int), (Int, Int))] -> Int -> Int -> [Int] -> Double
-- solve edges s t order = go 0.0 0 (fst (edges !! 0)) False  -- 初期地点は edges の最初の地点、acc は Double 型
--   where
--     go :: Double -> Int -> (Int, Int) -> Bool -> Double
--     go !acc !idx (!x, !y) !isOnEdge
--       | idx == length order = acc  -- 全ての辺を辿り終えたら終了
--       | otherwise =
--         let ((a, b), (c, d)) = edges !! (order !! idx - 1)  -- 順番に従って辺を取得
--             -- isOnEdgeがTrueの時、(x, y) から (c, d) へ移動
--             (distance, newPos, newIsOnEdge, weight) = 
--               if isOnEdge then 
--                 let dist = sqrt (fromIntegral ((x - c)^2 + (y - d)^2))  -- Double 型の距離計算
--                 in (dist, (c, d), False, fromIntegral t) -- 辺の上なので重さ t (Double に変換)
--               else
--                 let dist = sqrt (fromIntegral ((x - a)^2 + (y - b)^2))  -- Double 型の距離計算
--                 in (dist, (a, b), True, fromIntegral s) -- 辺の上でないので重さ s (Double に変換)
--             time = weight * distance
--             acc' = acc + time
--         in go acc' (idx + 1) newPos newIsOnEdge

-- main = do 
--   [n, s, t] <- getInts
--   info <- replicateM n getInts
--   -- info::[[Int]]をedges::[((Int,Int),(Int,Int))]に変換
--   let edges = concatMap (\[a,b,c,d] -> 
--                 [ ((a,b),(c,d))
--                 , ((c,d),(a,b))
--                 , ((b,a),(c,d))
--                 , ((d,c),(b,a))]) info

--   -- どの順番で辺を巡るかを全探索
--   let ans = minimum [solve edges s t order | order <- permutations [1..n]]

--   print ans

solve :: [((Int, Int), (Int, Int))] -> Int -> Int -> [Int] -> Double
solve edges s t order = go 0.0 0 (0, 0)
  where
    go :: Double -> Int -> (Int, Int) -> Double
    go !acc !idx (!x, !y)
      | idx == length order = acc 
      | otherwise = 
        let ((a, b), (c, d)) = edges !! (order !! idx)  -- 順番に従って次の辺を取得
            -- (a, b) に向かう場合
            -- 速度 s で (a, b) に移動し、その後、速度 t で (c, d) に移動
            (distance1, newPos1) = 
              let sDist = sqrt (fromIntegral ((x - a)^2 + (y - b)^2)) / fromIntegral s :: Double
                  tDist = sqrt (fromIntegral ((a - c)^2 + (b - d)^2)) / fromIntegral t :: Double
              in (sDist + tDist, (c, d))
            result1 = go (acc + distance1) (idx + 1) newPos1  -- 次の位置に移動して再帰

            -- (c, d) に向かう場合
            -- 速度 s で (c, d) に移動し、その後、速度 t で (a, b) に移動
            (distance2, newPos2) = 
              let sDist = sqrt (fromIntegral ((x - c)^2 + (y - d)^2)) / fromIntegral s :: Double
                  tDist = sqrt (fromIntegral ((c - a)^2 + (d - b)^2)) / fromIntegral t :: Double
              in (sDist + tDist, (a, b))
            result2 = go (acc + distance2) (idx + 1) newPos2  -- 次の位置に移動して再帰
        in -- traceShow (idx, (x, y), (a, b), (c, d), acc) $
           min result1 result2  -- 2通りの中で小さい方を選択


main = do 
  [n, s, t] <- getInts
  info <- replicateM n getInts
  -- info::[[Int]]をedges::[((Int, Int), (Int, Int))]に変換
  let edges = map (\[a, b, c, d] -> ((a, b), (c, d))) info
  
  -- どの順番で辺を巡るかを全探索
  -- 辺のどちらに向かうかで2通り
  let allOrders = permutations [0..n-1]
  let ans = minimum [solve edges s t order | order <- allOrders]

  print ans
  

{-- IO --}

yn :: Bool -> String
yn = bool "No" "Yes"

printYn :: Bool -> IO ()
printYn = putStrLn . yn

printTuple :: (Show a) => (a, a) -> IO ()
printTuple (i, j) = printList [i, j]

printList :: (Show a) => [a] -> IO ()
printList = putStrLn . unwords . map show

printFlush :: (Show a) => a -> IO ()
printFlush x = print x >> hFlush stdout

printListFlush :: (Show a) => [a] -> IO ()
printListFlush xs = printList xs >> hFlush stdout

putStrLnFlush :: String -> IO ()
putStrLnFlush s = putStrLn s >> hFlush stdout

getInt :: IO Int
getInt = fst . fromJust . BS.readInt <$> BS.getLine

getInteger :: IO Integer
getInteger = fst . fromJust . BS.readInteger <$> BS.getLine

getInts :: IO [Int]
getInts = unfoldr (BS.readInt . BS.dropWhile isSpace) <$> BS.getLine

getIntegers :: IO [Integer]
getIntegers = unfoldr (BS.readInteger . BS.dropWhile isSpace) <$> BS.getLine

getTuple :: IO (Int, Int)
getTuple = auto

getTuple3 :: IO (Int, Int, Int)
getTuple3 = auto

getWeightedEdge :: IO ((Int, Int), Int)
getWeightedEdge = do
  [u, v, w] <- getInts
  return ((u, v), w)

getIntArray :: (Int, Int) -> IO (UArray Int Int)
getIntArray b = listArray @UArray b <$> getInts

getCharArray :: (Int, Int) -> IO (UArray Int Char)
getCharArray b = listArray @UArray b <$> getLine

getStringArray :: IO (UArray Int Char)
getStringArray = do
  s <- BS.getLine
  return $ listArray @UArray (1, BS.length s) (BS.unpack s)

getCharGrid :: ((Int, Int), (Int, Int)) -> IO (UArray (Int, Int) Char)
getCharGrid b@((s, _), (h, _)) = do
  xs <- replicateM (h + 1 - s) BS.getLine
  return (listArray @UArray b $ BS.unpack $ BS.concat xs)

getIntGrid :: ((Int, Int), (Int, Int)) -> IO (UArray (Int, Int) Int)
getIntGrid b@((s, _), (h, _)) = do
  xs <- replicateM (h + 1 - s) getInts
  return (listArray @UArray b $ concat xs)

printCharGrid :: (IArray a Char, Ix v) => a (v, Int) Char -> IO ()
printCharGrid grid = traverse_ putStrLn $ chunksOf w (elems grid)
  where
    ((_, w1), (_, w2)) = bounds grid
    w = w2 + 1 - w1

printIntGrid :: (Show e, IArray a e, Ix v) => a (v, Int) e -> IO ()
printIntGrid grid = traverse_ (putStrLn . unwords . map show) $ chunksOf w (elems grid)
  where
    ((_, w1), (_, w2)) = bounds grid
    w = w2 + 1 - w1

{-- auto --}
-- | Read from a space-delimited `ByteString`.
class ReadBS a where
  {-# INLINE convertBS #-}
  convertBS :: BS.ByteString -> a
  default convertBS :: (Read a) => BS.ByteString -> a
  convertBS = read . BS.unpack

  -- | For use with `U.unfoldrExactN`.
  {-# INLINE readBS #-}
  readBS :: BS.ByteString -> (a, BS.ByteString)
  readBS !bs =
    let (!bs1, !bs2) = BS.break isSpace bs
     in (convertBS bs1, bs2)

  -- | For use with `U.unfoldr`.
  {-# INLINE readMayBS #-}
  readMayBS :: BS.ByteString -> Maybe (a, BS.ByteString)
  readMayBS !bs
    | BS.null bs = Nothing
    | otherwise =
        let (!bs1, !bs2) = BS.break isSpace bs
         in Just (convertBS bs1, bs2)

instance ReadBS Int where
  {-# INLINE convertBS #-}
  convertBS = fst . readBS
  {-# INLINE readBS #-}
  readBS = fromJust . readMayBS
  {-# INLINE readMayBS #-}
  readMayBS = BS.readInt

instance ReadBS Integer where
  {-# INLINE convertBS #-}
  convertBS = fst . readBS
  {-# INLINE readBS #-}
  readBS = fromJust . readMayBS
  {-# INLINE readMayBS #-}
  readMayBS = BS.readInteger

instance ReadBS Float

instance ReadBS Double

instance ReadBS Char where
  {-# INLINE convertBS #-}
  convertBS = BS.head

instance ReadBS String where
  {-# INLINE convertBS #-}
  convertBS = BS.unpack

instance ReadBS BS.ByteString where
  {-# INLINE convertBS #-}
  convertBS = id

instance (ReadBS a1, ReadBS a2) => ReadBS (a1, a2) where
  {-# INLINE convertBS #-}
  convertBS !bs0 =
    let (!a1, !bs1) = readBS (BS.dropWhile isSpace bs0)
        !a2 = convertBS (BS.dropWhile isSpace bs1)
     in (a1, a2)
  {-# INLINE readBS #-}
  readBS = fromJust . readMayBS
  {-# INLINE readMayBS #-}
  readMayBS !bs0 = do
    (!x1, !bs1) <- readMayBS bs0
    (!x2, !bs2) <- readMayBS bs1
    Just ((x1, x2), bs2)

instance (ReadBS a1, ReadBS a2, ReadBS a3) => ReadBS (a1, a2, a3) where
  {-# INLINE convertBS #-}
  convertBS !bs0 =
    let (!a1, !bs1) = readBS (BS.dropWhile isSpace bs0)
        (!a2, !bs2) = readBS (BS.dropWhile isSpace bs1)
        !a3 = convertBS (BS.dropWhile isSpace bs2)
     in (a1, a2, a3)
  {-# INLINE readBS #-}
  readBS = fromJust . readMayBS
  {-# INLINE readMayBS #-}
  readMayBS !bs0 = do
    (!x1, !bs1) <- readMayBS bs0
    (!x2, !bs2) <- readMayBS bs1
    (!x3, !bs3) <- readMayBS bs2
    Just ((x1, x2, x3), bs3)

-- instance (ReadBS a1, ReadBS a2, ReadBS a3, ReadBS a4) => ReadBS (a1, a2, a3, a4) where
--   {-# INLINE convertBS #-}
--   convertBS !bs0 =
--     let (!a1, !bs1) = readBS (BS.dropWhile isSpace bs0)
--         (!a2, !bs2) = readBS (BS.dropWhile isSpace bs1)
--         (!a3, !bs3) = readBS (BS.dropWhile isSpace bs2)
--         !a4 = convertBS (BS.dropWhile isSpace bs3)
--      in (a1, a2, a3, a4)
--   {-# INLINE readBS #-}
--   readBS = fromJust . readMayBS
--   {-# INLINE readMayBS #-}
--   readMayBS !bs0 = do
--     (!x1, !bs1) <- readMayBS bs0
--     (!x2, !bs2) <- readMayBS bs1
--     (!x3, !bs3) <- readMayBS bs2
--     (!x4, !bs4) <- readMayBS bs3
--     Just ((x1, x2, x3, x4), bs4)

-- | Parses one line via the `ReadBS` class.
auto :: (ReadBS a) => IO a
auto = convertBS <$> BS.getLine


{-- Tuple --}

instance (Num a) => Num (a, a) where
  (x1, x2) + (y1, y2) = (x1 + y1, x2 + y2)
  (x1, x2) - (y1, y2) = (x1 - y1, x2 - y2)
  (x1, x2) * (y1, y2) = (x1 * y1, x2 * y2)
  negate (x1, x2) = (negate x1, negate x2)
  abs (x1, x2) = (abs x1, abs x2)
  signum (x1, x2) = (signum x1, signum x2)
  fromInteger n = (fromInteger n, fromInteger n)

filterOnFst :: (a -> Bool) -> [(a, b)] -> [(a, b)]
filterOnFst f = filter (f . fst)

filterOnSnd :: (b -> Bool) -> [(a, b)] -> [(a, b)]
filterOnSnd f = filter (f . snd)

findOnFst :: (Foldable t) => (b1 -> Bool) -> t (b1, b2) -> Maybe (b1, b2)
findOnFst f = find (f . fst)

findOnSnd :: (Foldable t) => (b -> Bool) -> t (a, b) -> Maybe (a, b)
findOnSnd f = find (f . snd)

rotateRight :: (Num b) => (b, a) -> (a, b)
rotateRight (h, w) = (w, -h)
{-# INLINE rotateRight #-}

rotateLeft :: (Num a) => (b, a) -> (a, b)
rotateLeft (h, w) = (-w, h)
{-# INLINE rotateLeft #-}


{-- MArray --}
-- 配列内の2つの要素を入れ替える関数
swapArray :: (MArray a e m, Ix i) => a i e -> i -> i -> m ()
swapArray as i j = do
  a <- readArray as i
  b <- readArray as j
  writeArray as j $! a
  writeArray as i $! b
{-# INLINE swapArray #-}

{-- Run Length --}

rle :: Eq a => [a] -> [(a, Int)]
rle = map (\x -> (head x, length x)) . group

rleOn :: Eq b => (a -> b) -> [a] -> [(a, Int)]
rleOn f = map (\g -> (head g, length g)) . groupOn f

rleBS :: BS.ByteString -> [(Char, Int)]
rleBS = map (\x -> (BS.head x, BS.length x)) . BS.group

-- {{{ Debugging
#ifndef ATCODER
dbg :: Show a => a -> ()
dbg !x = let !_ = traceShow x () in ()

dbgAssert :: Bool -> a -> a
dbgAssert False !x = error "assertion failed!"
dbgAssert True !x = x

#else
dbg :: Show a => a -> ()
dbg !_ = ()

dbgAssert :: Bool -> a -> a
dbgAssert = flip const

#endif

getDebugEnv :: Maybe String
getDebugEnv = unsafePerformIO (lookupEnv "DEBUG")
{-# NOINLINE getDebugEnv #-}
-- }}}

提出情報

提出日時
問題 D - Laser Marking
ユーザ suupia
言語 Haskell (GHC 9.4.5)
得点 350
コード長 15689 Byte
結果 AC
実行時間 4 ms
メモリ 7672 KiB

コンパイルエラー

app/Main.hs:166:54: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:166:54
        (Num b0) arising from the literal ‘2’ at app/Main.hs:166:55
    • In the first argument of ‘(+)’, namely ‘(x - a) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((x - a) ^ 2 + (y - b) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((x - a) ^ 2 + (y - b) ^ 2))’
    |
166 |               let sDist = sqrt (fromIntegral ((x - a)^2 + (y - b)^2)) / fromIntegral s :: Double
    |                                                      ^

app/Main.hs:166:66: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:166:66
        (Num b0) arising from the literal ‘2’ at app/Main.hs:166:67
    • In the second argument of ‘(+)’, namely ‘(y - b) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((x - a) ^ 2 + (y - b) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((x - a) ^ 2 + (y - b) ^ 2))’
    |
166 |               let sDist = sqrt (fromIntegral ((x - a)^2 + (y - b)^2)) / fromIntegral s :: Double
    |                                                                  ^

app/Main.hs:167:54: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:167:54
        (Num b0) arising from the literal ‘2’ at app/Main.hs:167:55
    • In the first argument of ‘(+)’, namely ‘(a - c) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((a - c) ^ 2 + (b - d) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((a - c) ^ 2 + (b - d) ^ 2))’
    |
167 |                   tDist = sqrt (fromIntegral ((a - c)^2 + (b - d)^2)) / fromIntegral t :: Double
    |                                                      ^

app/Main.hs:167:66: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:167:66
        (Num b0) arising from the literal ‘2’ at app/Main.hs:167:67
    • In the second argument of ‘(+)’, namely ‘(b - d) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((a - c) ^ 2 + (b - d) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((a - c) ^ 2 + (b - d) ^ 2))’
    |
167 |                   tDist = sqrt (fromIntegral ((a - c)^2 + (b - d)^2)) / fromIntegral t :: Double
    |                                                                  ^

app/Main.hs:174:54: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:174:54
        (Num b0) arising from the literal ‘2’ at app/Main.hs:174:55
    • In the first argument of ‘(+)’, namely ‘(x - c) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((x - c) ^ 2 + (y - d) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((x - c) ^ 2 + (y - d) ^ 2))’
    |
174 |               let sDist = sqrt (fromIntegral ((x - c)^2 + (y - d)^2)) / fromIntegral s :: Double
    |                                                      ^

app/Main.hs:174:66: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:174:66
        (Num b0) arising from the literal ‘2’ at app/Main.hs:174:67
    • In the second argument of ‘(+)’, namely ‘(y - d) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((x - c) ^ 2 + (y - d) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((x - c) ^ 2 + (y - d) ^ 2))’
    |
174 |               let sDist = sqrt (fromIntegral ((x - c)^2 + (y - d)^2)) / fromIntegral s :: Double
    |                                                                  ^

app/Main.hs:175:54: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:175:54
        (Num b0) arising from the literal ‘2’ at app/Main.hs:175:55
    • In the first argument of ‘(+)’, namely ‘(c - a) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((c - a) ^ 2 + (d - b) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((c - a) ^ 2 + (d - b) ^ 2))’
    |
175 |                   tDist = sqrt (fromIntegral ((c - a)^2 + (d - b)^2)) / fromIntegral t :: Double
    |                                                      ^

app/Main.hs:175:66: warning: [-Wtype-defaults]
    • Defaulting the type variable ‘b0’ to type ‘Integer’ in the following constraints
        (Integral b0) arising from a use of ‘^’ at app/Main.hs:175:66
        (Num b0) arising from the literal ‘2’ at app/Main.hs:175:67
    • In the second argument of ‘(+)’, namely ‘(d - b) ^ 2’
      In the first argument of ‘fromIntegral’, namely
        ‘((c - a) ^ 2 + (d - b) ^ 2)’
      In the first argument of ‘sqrt’, namely
        ‘(fromIntegral ((c - a) ^ 2 + (d - b) ^ 2))’
    |
175 |                   tDist = sqrt (fromIntegral ((c - a)^2 + (d - b)^2)) / fromIntegral t :: Double
    |                                                                  ^

app/Main.hs:182:1: warning: [-Wmissing-signatures]
    Top-level binding with no type signature: main :: IO ()
    |
182 | main = do 
    | ^^^^

app/Main.hs:186:20: warning: [-Wincomplete-uni-patterns]
    Pattern match(es) are non-exhaustive
    In a lambda abstraction:
        Patterns of type ‘[Int]’ not matched:
            []
            [_]
            [_, _]
            [_, _, _]
            ...
    |
186 |   let edges = map (\[a, b, c, d] -> ((a, b), (c, d))) info
    |                    ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

ジャッジ結果

セット名 Sample All
得点 / 配点 0 / 0 350 / 350
結果
AC × 4
AC × 74
セット名 テストケース
Sample sample_01.txt, sample_02.txt, sample_03.txt, sample_04.txt
All sample_01.txt, sample_02.txt, sample_03.txt, sample_04.txt, test_01.txt, test_02.txt, test_03.txt, test_04.txt, test_05.txt, test_06.txt, test_07.txt, test_08.txt, test_09.txt, test_10.txt, test_11.txt, test_12.txt, test_13.txt, test_14.txt, test_15.txt, test_16.txt, test_17.txt, test_18.txt, test_19.txt, test_20.txt, test_21.txt, test_22.txt, test_23.txt, test_24.txt, test_25.txt, test_26.txt, test_27.txt, test_28.txt, test_29.txt, test_30.txt, test_31.txt, test_32.txt, test_33.txt, test_34.txt, test_35.txt, test_36.txt, test_37.txt, test_38.txt, test_39.txt, test_40.txt, test_41.txt, test_42.txt, test_43.txt, test_44.txt, test_45.txt, test_46.txt, test_47.txt, test_48.txt, test_49.txt, test_50.txt, test_51.txt, test_52.txt, test_53.txt, test_54.txt, test_55.txt, test_56.txt, test_57.txt, test_58.txt, test_59.txt, test_60.txt, test_61.txt, test_62.txt, test_63.txt, test_64.txt, test_65.txt, test_66.txt, test_67.txt, test_68.txt, test_69.txt, test_70.txt
ケース名 結果 実行時間 メモリ
sample_01.txt AC 2 ms 7180 KiB
sample_02.txt AC 2 ms 7176 KiB
sample_03.txt AC 3 ms 7600 KiB
sample_04.txt AC 3 ms 7528 KiB
test_01.txt AC 1 ms 7208 KiB
test_02.txt AC 2 ms 7112 KiB
test_03.txt AC 1 ms 7128 KiB
test_04.txt AC 1 ms 7024 KiB
test_05.txt AC 3 ms 7636 KiB
test_06.txt AC 2 ms 7156 KiB
test_07.txt AC 2 ms 7208 KiB
test_08.txt AC 1 ms 7112 KiB
test_09.txt AC 1 ms 7172 KiB
test_10.txt AC 2 ms 7280 KiB
test_11.txt AC 3 ms 7608 KiB
test_12.txt AC 1 ms 7180 KiB
test_13.txt AC 1 ms 7176 KiB
test_14.txt AC 1 ms 6944 KiB
test_15.txt AC 2 ms 6960 KiB
test_16.txt AC 2 ms 7256 KiB
test_17.txt AC 3 ms 7672 KiB
test_18.txt AC 1 ms 7144 KiB
test_19.txt AC 2 ms 7172 KiB
test_20.txt AC 1 ms 7148 KiB
test_21.txt AC 1 ms 7164 KiB
test_22.txt AC 1 ms 7224 KiB
test_23.txt AC 3 ms 7632 KiB
test_24.txt AC 1 ms 7100 KiB
test_25.txt AC 2 ms 6928 KiB
test_26.txt AC 1 ms 7104 KiB
test_27.txt AC 2 ms 6964 KiB
test_28.txt AC 2 ms 7252 KiB
test_29.txt AC 4 ms 7560 KiB
test_30.txt AC 1 ms 7104 KiB
test_31.txt AC 1 ms 7176 KiB
test_32.txt AC 1 ms 7152 KiB
test_33.txt AC 1 ms 7124 KiB
test_34.txt AC 2 ms 7148 KiB
test_35.txt AC 3 ms 7392 KiB
test_36.txt AC 2 ms 7172 KiB
test_37.txt AC 1 ms 7176 KiB
test_38.txt AC 2 ms 6948 KiB
test_39.txt AC 1 ms 7188 KiB
test_40.txt AC 2 ms 7240 KiB
test_41.txt AC 3 ms 7352 KiB
test_42.txt AC 2 ms 7176 KiB
test_43.txt AC 1 ms 7144 KiB
test_44.txt AC 1 ms 7108 KiB
test_45.txt AC 2 ms 7228 KiB
test_46.txt AC 2 ms 7240 KiB
test_47.txt AC 3 ms 7528 KiB
test_48.txt AC 2 ms 7176 KiB
test_49.txt AC 1 ms 7172 KiB
test_50.txt AC 2 ms 7216 KiB
test_51.txt AC 1 ms 7152 KiB
test_52.txt AC 2 ms 7252 KiB
test_53.txt AC 3 ms 7400 KiB
test_54.txt AC 2 ms 7104 KiB
test_55.txt AC 2 ms 7104 KiB
test_56.txt AC 2 ms 7120 KiB
test_57.txt AC 1 ms 7192 KiB
test_58.txt AC 2 ms 7240 KiB
test_59.txt AC 4 ms 7660 KiB
test_60.txt AC 1 ms 7156 KiB
test_61.txt AC 4 ms 7568 KiB
test_62.txt AC 3 ms 7400 KiB
test_63.txt AC 2 ms 7212 KiB
test_64.txt AC 1 ms 7124 KiB
test_65.txt AC 3 ms 7396 KiB
test_66.txt AC 3 ms 7528 KiB
test_67.txt AC 4 ms 7528 KiB
test_68.txt AC 4 ms 7484 KiB
test_69.txt AC 4 ms 7604 KiB
test_70.txt AC 4 ms 7596 KiB