module FileFormat.TSPLIB( loadTSPFile )where -- only supports a subset of the TSPLIB format -- not using real parsing libraries. This is probably a mistake. -- also, still not using ByteString, also a misake. import CombinatorialOptimisation.TSP -- load save of TSPLIB -- can only resave explicit data, could be cripling for big -- data sets -- for those files where the co-ordinates of nodes are given euclidianDistance :: (Float,Float)->(Float,Float)->Float euclidianDistance (a,b) (c,d) = sqrt ((a-c)*(a-c)+(b-d)*(b-d)) geoDistance :: (Float,Float)->(Float,Float)->Float geoDistance (x1,y1) (x2,y2) = encodeFloat (floor dij) 0 where q1 = cos (lon1 - lon2) q2 = cos (lat1 - lat2) q3 = cos (lat1 + lat2) lon1 = degConvert y1 lon2 = degConvert y2 lat1 = degConvert x1 lat2 = degConvert x2 dij = 6378.388 * (acos( 0.5*((1.0+q1)*q2 - ((1.0-q1)*q3) )) ) + 1.0 degConvert m = let deg = encodeFloat (floor m) 0 miN = m - deg in 3.141592 * (deg + (5.0 * miN/3.0))/180.0 {- readSpecification :: String->([(String,String)],String) readSpecification s | name -> print? | type -> TSP or ATSP only | comment -> throw or print | dimension Int | capacity, not interested | edge-weight-type -> Lots | edge-weight-format | edge-data-format | node-coord-type | display-data-type | eof: end do not expect -} data Specification = IGNORE String | USEFUL String String | ENDSPEC String | FAIL String deriving Show isUsefulSpec (USEFUL _ _) = True isUsefulSpec _ = False readSpecificationLine :: String->Specification readSpecificationLine s | likeString "NAME" s = IGNORE s | likeString "TYPE" s = USEFUL "Type" (trim s) | likeString "NODE_COORD_SECTION" s = ENDSPEC "NODE COORD" | likeString "EDGE_WEIGHT_SECTION" s = ENDSPEC "EDGE WEIGHT" | likeString "COMMENT" s = IGNORE s | likeString "DIMENSION" s = USEFUL "Dimension" (trim s) | likeString "DISPLAY_DATA_TYPE" s = IGNORE s | likeString "EDGE_WEIGHT_TYPE" s = USEFUL "EdgeWeightType" (trim s) | otherwise = FAIL $ "unrecognised field in specification : "++s where likeString q s = take (length q) s == q trim s = let s' = (dropWhile (==' ')) . (drop 1) . (dropWhile (/=':')) $ s in reverse . (dropWhile (==' ')) . reverse $ s' readSpecification :: [String]->([Specification],[String]) readSpecification [] = ([FAIL "seem to have run out of data, without ending the specification phase"],[]) readSpecification (s:ss) = let p = readSpecificationLine s (rs,es) = readSpecification ss in case p of ENDSPEC k -> ([USEFUL "DATA PART TYPE" k],ss) IGNORE _ -> (p:rs,es) FAIL _ -> (p:rs,es) USEFUL _ _ -> (p:rs,es) loadTSPFile :: String->IO () -- TSPProblem loadTSPFile fName = do rawContents<-readFile fName let (spec,remainder) = readSpecification $ lines rawContents mapM_ print spec print "" mapM_ print $ filter isUsefulSpec spec {- readEdgeWeightSection FULL_MATRIX readEdgeWeightSection :: Num a=>String->Int->String->IO (Int->Int->Float) readEdgeWeightSection ty dim inputData = do readNodeCoordSection :: Num a=>String->Int->String->IO (Int->Int->Float) readNodeCoordSection dim inputData = do -}